-- 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/SVGImage.chs" #-}
{-# LANGUAGE OverloadedStrings, CPP, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.SVGImage
    (
     svgImageNew,
     svgImageNewFromFile
     -- * Hierarchy
     --
     -- $hierarchy

    )
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_Types
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Hierarchy
import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
import Graphics.UI.FLTK.LowLevel.Dispatch
import Graphics.UI.FLTK.LowLevel.RGBImage
import qualified Data.Text as T
import qualified Data.ByteString as B

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

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

svgImageNewFromFile :: T.Text -> IO (Either UnknownError (Ref SVGImage))
svgImageNewFromFile path' = do
  pathPtr <- copyTextToCString path'
  ptr <- svgImageNewWithData' pathPtr (castPtr nullPtr)
  ref' <- (toRef ptr :: IO (Ref SVGImage))
  checkImage ref'

svgImageNew :: B.ByteString -> IO (Either UnknownError (Ref SVGImage))
svgImageNew svgData' =
  B.useAsCString svgData' (\dataPtr -> do
    ptr <- svgImageNewWithData' (castPtr nullPtr) dataPtr
    ref' <- (toRef ptr :: IO (Ref SVGImage))
    checkImage ref'
  )

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

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

instance (impl ~ (IO ())) => Op (Destroy ()) SVGImage orig impl where
  runOp _ _ image = withRef image $ \imagePtr -> flImageDestroy' imagePtr

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

{-# LINE 46 "src/Graphics/UI/FLTK/LowLevel/SVGImage.chs" #-}

instance (impl ~ ( Size -> IO ())) => Op (Resize ()) SVGImage orig impl where
  runOp _ _ widget (Size (Width w') (Height h')) =
    withRef widget $ \widgetPtr -> resize' widgetPtr w' h'

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 51 "src/Graphics/UI/FLTK/LowLevel/SVGImage.chs" #-}

instance (impl ~ (Size -> IO (Maybe (Ref SVGImage)))) => Op (Copy ()) SVGImage orig impl where
  runOp _ _ image size' = case size' of
    (Size (Width imageWidth) (Height imageHeight)) ->
        withRef image $ \imagePtr -> copyWithWH' imagePtr imageWidth imageHeight >>= 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 57 "src/Graphics/UI/FLTK/LowLevel/SVGImage.chs" #-}

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

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

{-# LINE 61 "src/Graphics/UI/FLTK/LowLevel/SVGImage.chs" #-}

instance (impl ~ ( IO ())) => Op (Desaturate ()) SVGImage 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 65 "src/Graphics/UI/FLTK/LowLevel/SVGImage.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 66 "src/Graphics/UI/FLTK/LowLevel/SVGImage.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 67 "src/Graphics/UI/FLTK/LowLevel/SVGImage.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 68 "src/Graphics/UI/FLTK/LowLevel/SVGImage.chs" #-}


instance (impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ())) => Op (DrawResize ()) SVGImage 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 82 "src/Graphics/UI/FLTK/LowLevel/SVGImage.chs" #-}

instance (impl ~ (Position ->  IO ())) => Op (Draw ()) SVGImage orig impl where
  runOp _ _ image (Position (X x_pos') (Y y_pos')) = withRef image $ \imagePtr -> draw' imagePtr x_pos' y_pos'

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

-- $functions
-- @
-- colorAverage :: 'Ref' 'SVGImage' -> 'Color' -> 'Float' -> 'IO' ()
--
-- copy :: 'Ref' 'SVGImage' -> 'Size' -> 'IO' ('Maybe' ('Ref' 'SVGImage'))
--
-- desaturate :: 'Ref' 'SVGImage' -> 'IO' ()
--
-- destroy :: 'Ref' 'SVGImage' -> 'IO' ()
--
-- draw :: 'Ref' 'SVGImage' -> 'Position' -> 'IO' ()
--
-- drawResize :: 'Ref' 'SVGImage' -> 'Position' -> 'Size' -> 'Maybe' 'X' -> 'Maybe' 'Y' -> 'IO' ()
--
-- resize :: 'Ref' 'SVGImage' -> 'Size' -> 'IO' ()
-- @

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/SVGImage.chs.h Fl_SVG_Image_New_WithData"
  svgImageNewWithData''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr ()))))

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

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

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

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

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

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

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