-- GENERATED by C->Haskell Compiler, version 0.28.1 Switcheroo, 1 April 2016 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Image
       (
       ImageFuncs(..),
       defaultImageFuncs,
       imageNew,
       ColorAverageCallback,
       ImageDrawCallback,
       ImageCopyCallback,
       toImageDrawCallbackPrim,
       toColorAverageCallbackPrim,
       toImageCopyCallbackPrim
       -- * Hierarchy
       --
       -- $hierarchy

       -- * Functions
       --
       -- $functions
       )
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable 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


type ColorAverageCallback        = Ref Image -> Color -> Float -> IO ()
type ImageDrawCallback           = Ref Image -> Position -> Size -> Maybe X -> Maybe Y -> IO ()
type ImageCopyCallback           = Ref Image -> Size -> IO (Ref Image)
toImageDrawCallbackPrim :: ImageDrawCallback -> IO (FunPtr ImageDrawCallbackPrim)
toImageDrawCallbackPrim f =
    mkImageDrawCallbackPrimPtr
    (\ptr x_pos' y_pos' width' height' x_offset' y_offset' ->
       let _x_offset = fmap X $ integralToMaybe x_offset'
           _y_offset = fmap Y $ integralToMaybe y_offset'
           position' = Position (X $ fromIntegral x_pos')
                                (Y $ fromIntegral y_pos')
           size' = Size (Width $ fromIntegral width')
                        (Height $ fromIntegral height')
       in
        toRef ptr >>= \refPtr -> f refPtr position' size' _x_offset _y_offset
    )

toColorAverageCallbackPrim :: ColorAverageCallback -> IO (FunPtr ColorAverageCallbackPrim)
toColorAverageCallbackPrim f =
    mkColorAverageCallbackPtr
    (\ptr cint cfloat ->
         wrapNonNull ptr "Null pointer. toColorAverageCallbackPrim" >>= \pp ->
         f (wrapInRef pp) (Color (fromIntegral cint)) (realToFrac cfloat)
    )

toImageCopyCallbackPrim :: ImageCopyCallback -> IO (FunPtr ImageCopyCallbackPrim)
toImageCopyCallbackPrim f =
    mkImageCopyCallbackPrimPtr
    (\ptr width' height' -> do
         pp <- wrapNonNull ptr "Null pointer. toImageCopyCallbackPrim"
         refPtr <- f (wrapInRef pp) (Size (Width $ fromIntegral width')
                                           (Height $ fromIntegral height'))
         unsafeRefToPtr refPtr
    )


data ImageFuncs a b =
  ImageFuncs
  {
    imageDrawOverride  :: Maybe (ImageDrawCallback),
    imageColorAverageOverride :: Maybe (ColorAverageCallback),
    imageCopyOverride :: Maybe (ImageCopyCallback),
    imageDesaturateOverride :: Maybe (Ref Image -> IO ()),
    imageUncacheOverride :: Maybe (Ref Image -> IO ())
  }

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

{-# LINE 92 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

imageFunctionStruct :: (ImageFuncs a b) -> IO (Ptr ())
imageFunctionStruct funcs = do
  p <- virtualFuncs'
  toImageDrawCallbackPrim `orNullFunPtr` (imageDrawOverride funcs) >>=
                            (\ptr val -> do {C2HSImp.pokeByteOff ptr 24 (val :: (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))))))}) p
  toColorAverageCallbackPrim `orNullFunPtr` (imageColorAverageOverride funcs) >>=
                            (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (C2HSImp.CFloat -> (IO ()))))))}) p
  toImageCopyCallbackPrim `orNullFunPtr` (imageCopyOverride funcs) >>=
                            (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))))}) p
  toCallbackPrim `orNullFunPtr` (imageDesaturateOverride funcs) >>=
                            (\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))))}) p
  toCallbackPrim `orNullFunPtr` (imageUncacheOverride funcs) >>=
                            (\ptr val -> do {C2HSImp.pokeByteOff ptr 32 (val :: (C2HSImp.FunPtr ((C2HSImp.Ptr ()) -> (IO ()))))}) p
  return p

defaultImageFuncs :: ImageFuncs a b
defaultImageFuncs = ImageFuncs Nothing Nothing Nothing Nothing Nothing

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

{-# LINE 111 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

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

{-# LINE 112 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

imageNew :: Size -> Depth -> Maybe (ImageFuncs a b) -> IO (Ref Image)
imageNew (Size (Width width') (Height height')) (Depth depth') funcs =
  case funcs of
    Just fs -> do
            fptr <- imageFunctionStruct fs
            obj <- flOverriddenImageNew' width' height' depth' (castPtr fptr)
            toRef obj
    Nothing -> flImageNew' width' height' depth' >>= toRef


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

{-# LINE 123 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ (IO ())) => Op (Destroy ()) Image 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 126 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetW ()) Image 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 129 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetH ()) Image 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 132 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetD ()) Image 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 135 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetLd ()) Image 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 138 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ ( IO (Int))) => Op (GetCount ()) Image 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 142 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

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

{-# LINE 143 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ ( Maybe Size -> IO (Maybe (Ref Image)))) => Op (Copy ()) Image 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 150 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ (Color -> Float ->  IO ())) => Op (ColorAverage ()) Image 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 154 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

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

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

{-# LINE 158 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ ( IO ())) => Op (Desaturate ()) Image 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 162 "src/Graphics/UI/FLTK/LowLevel/Image.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 163 "src/Graphics/UI/FLTK/LowLevel/Image.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 164 "src/Graphics/UI/FLTK/LowLevel/Image.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 165 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}


instance (impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ())) => Op (DrawResize ()) Image 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' a1 a2 a3 =
  let {a1' = id a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  draw''_ a1' a2' a3' >>
  return ()

{-# LINE 179 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

instance (impl ~ (Position ->  IO ())) => Op (Draw ()) Image 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 182 "src/Graphics/UI/FLTK/LowLevel/Image.chs" #-}

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


-- $functions
-- @
-- colorAverage :: 'Ref' 'Image' -> 'Color' -> 'Float' -> 'IO' ()
--
-- copy :: 'Ref' 'Image' -> 'Maybe' 'Size' -> 'IO' ('Maybe' ('Ref' 'Image'))
--
-- desaturate :: 'Ref' 'Image' -> 'IO' ()
--
-- destroy :: 'Ref' 'Image' -> 'IO' ()
--
-- draw :: 'Ref' 'Image' -> 'Position' -> 'IO' ()
--
-- drawResize :: 'Ref' 'Image' -> 'Position' -> 'Size' -> 'Maybe' 'X' -> 'Maybe' 'Y' -> 'IO' ()
--
-- getCount :: 'Ref' 'Image' -> 'IO' ('Int')
--
-- getD :: 'Ref' 'Image' -> 'IO' ('Int')
--
-- getH :: 'Ref' 'Image' -> 'IO' ('Int')
--
-- getLd :: 'Ref' 'Image' -> 'IO' ('Int')
--
-- getW :: 'Ref' 'Image' -> 'IO' ('Int')
--
-- inactive :: 'Ref' 'Image' -> 'IO' ()
--
-- uncache :: 'Ref' 'Image' -> 'IO' ()
--
-- Available in FLTK 1.3.4 only:
-- fail :: 'Ref' 'Image' -> 'IO' ('Either' 'ImageFail' ())
-- @

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

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Image.chs.h Fl_Image_default_virtual_funcs"
  virtualFuncs''_ :: (IO (C2HSImp.Ptr ()))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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