{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.Bitmap
(
bitmapNew
)
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
flBitmapNew' :: (Ptr CChar) -> (Int) -> (Int) -> IO ((Ptr ()))
flBitmapNew' a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
flBitmapNew''_ a1' a2' a3' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 25 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
bitmapNew :: BitmapHs -> IO (Ref Bitmap)
bitmapNew bitmap = withBitmap bitmap (\ptr width' height' -> flBitmapNew' ptr width' height' >>= toRef)
flBitmapDestroy' :: (Ptr ()) -> IO ((()))
flBitmapDestroy' a1 =
let {a1' = id a1} in
flBitmapDestroy''_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 28 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ (IO ())) => Op (Destroy ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> flBitmapDestroy' bitmapPtr
w' :: (Ptr ()) -> IO ((Int))
w' a1 =
let {a1' = id a1} in
w''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 31 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO (Int))) => Op (GetW ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> w' bitmapPtr
h' :: (Ptr ()) -> IO ((Int))
h' a1 =
let {a1' = id a1} in
h''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 34 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO (Int))) => Op (GetH ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> h' bitmapPtr
d' :: (Ptr ()) -> IO ((Int))
d' a1 =
let {a1' = id a1} in
d''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 37 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO (Int))) => Op (GetD ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> d' bitmapPtr
ld' :: (Ptr ()) -> IO ((Int))
ld' a1 =
let {a1' = id a1} in
ld''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 40 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO (Int))) => Op (GetLd ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> ld' bitmapPtr
count' :: (Ptr ()) -> IO ((Int))
count' a1 =
let {a1' = id a1} in
count''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 43 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO (Int))) => Op (GetCount ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> count' bitmapPtr
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 46 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
copy' :: (Ptr ()) -> IO ((Ptr ()))
copy' a1 =
let {a1' = id a1} in
copy''_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 47 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( Maybe Size -> IO (Maybe (Ref Bitmap)))) => Op (Copy ()) Bitmap orig impl where
runOp _ _ bitmap size' = case size' of
Just (Size (Width w) (Height h)) -> withRef bitmap $ \bitmapPtr -> copyWithWH' bitmapPtr w h >>= toMaybeRef
Nothing -> withRef bitmap $ \bitmapPtr -> copy' bitmapPtr >>= 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 52 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ (Color -> Float -> IO ())) => Op (ColorAverage ()) Bitmap orig impl where
runOp _ _ bitmap c i = withRef bitmap $ \bitmapPtr -> colorAverage' bitmapPtr c i
inactive' :: (Ptr ()) -> IO ()
inactive' a1 =
let {a1' = id a1} in
inactive''_ a1' >>
return ()
{-# LINE 55 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO ())) => Op (Inactive ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> inactive' bitmapPtr
desaturate' :: (Ptr ()) -> IO ()
desaturate' a1 =
let {a1' = id a1} in
desaturate''_ a1' >>
return ()
{-# LINE 58 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO ())) => Op (Desaturate ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> desaturate' bitmapPtr
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 62 "src/Graphics/UI/FLTK/LowLevel/Bitmap.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 63 "src/Graphics/UI/FLTK/LowLevel/Bitmap.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 64 "src/Graphics/UI/FLTK/LowLevel/Bitmap.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 65 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ())) => Op (DrawResize ()) Bitmap orig impl where
runOp _ _ bitmap (Position (X x) (Y y)) (Size (Width w) (Height h)) xOffset yOffset =
case (xOffset, yOffset) of
(Just (X xOff), Just (Y yOff)) ->
withRef bitmap $ \bitmapPtr -> drawWithCxCy' bitmapPtr x y w h (fromIntegral xOff) (fromIntegral yOff)
(Just (X xOff), Nothing) ->
withRef bitmap $ \bitmapPtr -> drawWithCx' bitmapPtr x y w h (fromIntegral xOff)
(Nothing, Just (Y yOff)) ->
withRef bitmap $ \bitmapPtr -> drawWithCy' bitmapPtr x y w h (fromIntegral yOff)
(Nothing, Nothing) ->
withRef bitmap $ \bitmapPtr -> drawWith' bitmapPtr 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 ()
{-# LINE 78 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ (Position -> IO ())) => Op (Draw ()) Bitmap 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 81 "src/Graphics/UI/FLTK/LowLevel/Bitmap.chs" #-}
instance (impl ~ ( IO ())) => Op (Uncache ()) Bitmap orig impl where
runOp _ _ bitmap = withRef bitmap $ \bitmapPtr -> uncache' bitmapPtr
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_New"
flBitmapNew''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_Destroy"
flBitmapDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_w"
w''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_h"
h''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_d"
d''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_ld"
ld''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_count"
count''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_copy_with_w_h"
copyWithWH''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_copy"
copy''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_color_average"
colorAverage''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (C2HSImp.CFloat -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_inactive"
inactive''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_desaturate"
desaturate''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_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/Bitmap.chs.h Fl_Bitmap_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/Bitmap.chs.h Fl_Bitmap_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/Bitmap.chs.h Fl_Bitmap_draw_with"
drawWith''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_draw"
draw''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Bitmap.chs.h Fl_Bitmap_uncache"
uncache''_ :: ((C2HSImp.Ptr ()) -> (IO ()))