-- GENERATED by C->Haskell Compiler, version 0.18.2 The shapeless maps, 31 Oct 2014 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}
{-# LANGUAGE CPP, FlexibleContexts #-}
module Graphics.UI.FLTK.LowLevel.Draw
       (
       flcSetColor,
       flcSetColorWithC,
       flcSetColorWithRgb,
       flcColor,
       flcPushClip,
       flcPushNoClip,
       flcPopClip,
       flcNotClipped,
       flcClipBox,
       flcRestoreClip,
       flcSetClipRegion,
       flcClipRegion,
       flcPoint,
       flcLineStyle,
       flcRect,
       flcRectWithColor,
       flcRectf,
       flcRectfWithColor,
       flcRectfWithRgb,
       flcLine,
       flcLineWithX2Y2,
       flcLoop,
       flcLoopWithX3Y3,
       flcPolygon,
       flcPolygonWithX3Y3,
       flcXyline,
       flcXylineWithX2,
       flcXylineWithY2X3,
       flcYxlineWithY1,
       flcYxlineWithY2X2,
       flcYxlineWithY2X3,
       flcArcByWidthHeight,
       flcPie,
       flcPushMatrix,
       flcPopMatrix,
       flcScaleWithY,
       flcScale,
       flcTranslate,
       flcRotate,
       flcMultMatrix,
       flcBeginPoints,
       flcBeginLine,
       flcBeginLoop,
       flcBeginPolygon,
       flcVertex,
       flcCurve,
       flcArcByRadius,
       flcCircle,
       flcEndPoints,
       flcEndLine,
       flcEndLoop,
       flcEndPolygon,
       flcBeginComplexPolygon,
       flcGap,
       flcEndComplexPolygon,
       flcTransformX,
       flcTransformY,
       flcTransformDx,
       flcTransformDy,
       flcTransformedVertex,
       flcSetFont,
       flcFont,
       flcSize,
       flcHeight,
       flcSetHeight,
       flcDescent,
       flcWidth,
       flcWidthWithN,
       flcWidthWithC,
       flcTextExtents,
       flcTextExtentsWithN,
       flcLatin1ToLocal,
       flcLatin1ToLocalWithN,
       flcLocalToLatin1,
       flcLocalToLatin1WithN,
       flcMacRomanToLocal,
       flcMacRomanToLocalWithN,
       flcLocalToMacRoman,
       flcLocalToMacRomanWithN,
       flcDraw,
       flcDrawWithAngle,
       flcDrawWithN,
       flcDrawWithNAngle,
       flcRtlDraw,
       flcMeasure,
       flcDrawInBoxWithImageReference,
       flcDrawInBox,
       flcFrame,
       flcFrame2,
       flcDrawBox,
       flcDrawImageBuf,
       flcDrawImageMonoBuf,
       flcCanDoAlphaBlending,
       flcReadImage,
       flcDrawPixmapWithColor,
       flcDrawPixmap,
       flcDrawPixmapWithCdataColor,
       flcDrawPixmapWithCdata,
       flcMeasurePixmap,
       flcMeasurePixmapWithCdata,
       flcShortcutLabel,
       flcOldShortcut,
       flcOverlayRect,
       flcOverlayClear,
       flcCursorWithFgBg,
       flcCursorWithFg,
       flcCursorWithBg,
       flcCursor,
       flcSetStatus,
       flcSetSpotWithWin,
       flcSetSpot,
       flcResetSpot,
       flcDrawSymbol
    )
where


import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Foreign.C
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Dispatch
import Graphics.UI.FLTK.LowLevel.Hierarchy
import Data.ByteString
import Data.ByteString.Unsafe

data LineStyle = SolidLineStyle
               | SolidDash
               | SolidDot
               | SolidDashDot
               | SolidDashDotDot
               | SolidCapFlat
               | SolidCapRound
               | SolidCapSquare
               | SolidJoinMiter
               | SolidJoinRound
               | SolidJoinBevel
  deriving (Show)
instance Enum LineStyle where
  succ SolidLineStyle = SolidDash
  succ SolidDash = SolidDot
  succ SolidDot = SolidDashDot
  succ SolidDashDot = SolidDashDotDot
  succ SolidDashDotDot = SolidCapFlat
  succ SolidCapFlat = SolidCapRound
  succ SolidCapRound = SolidCapSquare
  succ SolidCapSquare = SolidJoinMiter
  succ SolidJoinMiter = SolidJoinRound
  succ SolidJoinRound = SolidJoinBevel
  succ SolidJoinBevel = error "LineStyle.succ: SolidJoinBevel has no successor"

  pred SolidDash = SolidLineStyle
  pred SolidDot = SolidDash
  pred SolidDashDot = SolidDot
  pred SolidDashDotDot = SolidDashDot
  pred SolidCapFlat = SolidDashDotDot
  pred SolidCapRound = SolidCapFlat
  pred SolidCapSquare = SolidCapRound
  pred SolidJoinMiter = SolidCapSquare
  pred SolidJoinRound = SolidJoinMiter
  pred SolidJoinBevel = SolidJoinRound
  pred SolidLineStyle = error "LineStyle.pred: SolidLineStyle has no predecessor"

  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []

  enumFrom from = enumFromTo from SolidJoinBevel

  fromEnum SolidLineStyle = 0
  fromEnum SolidDash = 1
  fromEnum SolidDot = 2
  fromEnum SolidDashDot = 3
  fromEnum SolidDashDotDot = 4
  fromEnum SolidCapFlat = 256
  fromEnum SolidCapRound = 512
  fromEnum SolidCapSquare = 768
  fromEnum SolidJoinMiter = 4096
  fromEnum SolidJoinRound = 8192
  fromEnum SolidJoinBevel = 12288

  toEnum 0 = SolidLineStyle
  toEnum 1 = SolidDash
  toEnum 2 = SolidDot
  toEnum 3 = SolidDashDot
  toEnum 4 = SolidDashDotDot
  toEnum 256 = SolidCapFlat
  toEnum 512 = SolidCapRound
  toEnum 768 = SolidCapSquare
  toEnum 4096 = SolidJoinMiter
  toEnum 8192 = SolidJoinRound
  toEnum 12288 = SolidJoinBevel
  toEnum unmatched = error ("LineStyle.toEnum: Cannot match " ++ show unmatched)

{-# LINE 147 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}


flcSetColor' :: (Color) -> IO ()
flcSetColor' a1 =
  let {a1' = cFromColor a1} in 
  flcSetColor''_ a1' >>
  return ()

{-# LINE 149 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetColor :: Color ->  IO ()
flcSetColor c = flcSetColor' c

flcSetColorWithC' :: (Int) -> IO ()
flcSetColorWithC' a1 =
  let {a1' = fromIntegral a1} in 
  flcSetColorWithC''_ a1' >>
  return ()

{-# LINE 153 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetColorWithC :: Int ->  IO ()
flcSetColorWithC c = flcSetColorWithC' c

flcSetColorWithRgb' :: (Word8) -> (Word8) -> (Word8) -> IO ()
flcSetColorWithRgb' a1 a2 a3 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  flcSetColorWithRgb''_ a1' a2' a3' >>
  return ()

{-# LINE 157 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetColorWithRgb :: RGB ->  IO ()
flcSetColorWithRgb (r', g' , b') = flcSetColorWithRgb' r' g' b'

flcColor' :: IO ((Color))
flcColor' =
  flcColor''_ >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 161 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcColor ::  IO (Color)
flcColor  = flcColor'

flcPushClip' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcPushClip' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcPushClip''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 165 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPushClip :: Rectangle ->  IO ()
flcPushClip rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcPushClip' x_pos' y_pos' width' height'

flcPushNoClip' :: IO ()
flcPushNoClip' =
  flcPushNoClip''_ >>
  return ()

{-# LINE 169 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPushNoClip ::  IO ()
flcPushNoClip  = flcPushNoClip'

flcPopClip' :: IO ()
flcPopClip' =
  flcPopClip''_ >>
  return ()

{-# LINE 173 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPopClip ::  IO ()
flcPopClip  = flcPopClip'

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

{-# LINE 177 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcNotClipped :: Rectangle ->  IO (Int)
flcNotClipped rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcNotClipped' x_pos' y_pos' width' height'

flcClipBox' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ((Int), (Int), (Int), (Int), (Int))
flcClipBox' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  alloca $ \a5' -> 
  alloca $ \a6' -> 
  alloca $ \a7' -> 
  alloca $ \a8' -> 
  flcClipBox''_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  let {res' = fromIntegral res} in
  peekIntConv  a5'>>= \a5'' -> 
  peekIntConv  a6'>>= \a6'' -> 
  peekIntConv  a7'>>= \a7'' -> 
  peekIntConv  a8'>>= \a8'' -> 
  return (res', a5'', a6'', a7'', a8'')

{-# LINE 181 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcClipBox :: Rectangle ->  IO (Int,Rectangle)
flcClipBox rectangle  =
    let (x_pos', y_pos', width', height') = fromRectangle rectangle
    in
      do
        (result, _x', _y', _w', _h') <- flcClipBox' x_pos' y_pos' width' height'
        return $ (result, toRectangle (_x', _y', _w', _h'))

flcRestoreClip' :: IO ()
flcRestoreClip' =
  flcRestoreClip''_ >>
  return ()

{-# LINE 190 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRestoreClip ::  IO ()
flcRestoreClip  = flcRestoreClip'

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

{-# LINE 194 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetClipRegion :: Ref Region ->  IO ()
flcSetClipRegion r = withRef r $ \rPtr -> flcSetClipRegion' rPtr

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

{-# LINE 198 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcClipRegion ::  IO (Ref Region)
flcClipRegion  = flcClipRegion' >>= toRef

flcPoint' :: (Int) -> (Int) -> IO ()
flcPoint' a1 a2 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  flcPoint''_ a1' a2' >>
  return ()

{-# LINE 202 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPoint :: Position ->  IO ()
flcPoint (Position (X x_pos') (Y y_pos')) = flcPoint' x_pos' y_pos'

flcLineStyleWithWidthDashes' :: (LineStyle) -> (Int) -> (Ptr CChar) -> IO ()
flcLineStyleWithWidthDashes' a1 a2 a3 =
  let {a1' = cFromEnum a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = id a3} in 
  flcLineStyleWithWidthDashes''_ a1' a2' a3' >>
  return ()

{-# LINE 206 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLineStyle :: LineStyle -> Maybe Int -> Maybe String -> IO ()
flcLineStyle style width' dashes' = do
  let _width = maybe 0 id width'
  _dashes <- maybe (return nullPtr) newCString dashes'
  flcLineStyleWithWidthDashes' style _width _dashes

flcRect' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcRect' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcRect''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 213 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRect :: Rectangle ->  IO ()
flcRect rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcRect' x_pos' y_pos' width' height'

flcRectWithColor' :: (Int) -> (Int) -> (Int) -> (Int) -> (Color) -> IO ()
flcRectWithColor' a1 a2 a3 a4 a5 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = cFromColor a5} in 
  flcRectWithColor''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 217 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRectWithColor :: Rectangle -> Color ->  IO ()
flcRectWithColor rectangle c = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcRectWithColor' x_pos' y_pos' width' height' c

flcRectf' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcRectf' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcRectf''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 221 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRectf :: Rectangle ->  IO ()
flcRectf rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcRectf' x_pos' y_pos' width' height'

flcRectfWithColor' :: (Int) -> (Int) -> (Int) -> (Int) -> (Color) -> IO ()
flcRectfWithColor' a1 a2 a3 a4 a5 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = cFromColor a5} in 
  flcRectfWithColor''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 225 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRectfWithColor :: Rectangle -> Color ->  IO ()
flcRectfWithColor rectangle c = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcRectfWithColor' x_pos' y_pos' width' height' c

flcRectfWithRgb' :: (Int) -> (Int) -> (Int) -> (Int) -> (Word8) -> (Word8) -> (Word8) -> IO ()
flcRectfWithRgb' a1 a2 a3 a4 a5 a6 a7 =
  let {a1' = fromIntegral 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 
  flcRectfWithRgb''_ a1' a2' a3' a4' a5' a6' a7' >>
  return ()

{-# LINE 229 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRectfWithRgb :: Rectangle -> RGB ->  IO ()
flcRectfWithRgb rectangle (r', g' , b') = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcRectfWithRgb' x_pos' y_pos' width' height' r' g' b'

flcLine' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcLine' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcLine''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 233 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLine :: Position -> Position ->  IO ()
flcLine (Position (X x_pos') (Y y_pos'))(Position (X x_pos'') (Y y_pos''))  = flcLine' x_pos' y_pos' x_pos'' y_pos''

flcLineWithX2Y2' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcLineWithX2Y2' a1 a2 a3 a4 a5 a6 =
  let {a1' = fromIntegral 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 
  flcLineWithX2Y2''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 237 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLineWithX2Y2 :: Position -> Int -> Int -> Int -> Int ->  IO ()
flcLineWithX2Y2 (Position (X x_pos') (Y y_pos')) x1 y1 x2 y2 = flcLineWithX2Y2' x_pos' y_pos' x1 y1 x2 y2

flcLoop' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcLoop' a1 a2 a3 a4 a5 a6 =
  let {a1' = fromIntegral 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 
  flcLoop''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 241 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLoop :: Position -> Int -> Int -> Int -> Int ->  IO ()
flcLoop (Position (X x_pos') (Y y_pos')) x1 y1 x2 y2 = flcLoop' x_pos' y_pos' x1 y1 x2 y2

flcLoopWithX3Y3' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcLoopWithX3Y3' a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = fromIntegral 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 
  let {a8' = fromIntegral a8} in 
  flcLoopWithX3Y3''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  return ()

{-# LINE 245 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLoopWithX3Y3 :: Position -> Int -> Int -> Int -> Int -> Int -> Int ->  IO ()
flcLoopWithX3Y3 (Position (X x_pos') (Y y_pos')) x1 y1 x2 y2 x3 y3 = flcLoopWithX3Y3' x_pos' y_pos' x1 y1 x2 y2 x3 y3

flcPolygon' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcPolygon' a1 a2 a3 a4 a5 a6 =
  let {a1' = fromIntegral 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 
  flcPolygon''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 249 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPolygon :: Position -> Int -> Int -> Int -> Int ->  IO ()
flcPolygon (Position (X x_pos') (Y y_pos')) x1 y1 x2 y2 = flcPolygon' x_pos' y_pos' x1 y1 x2 y2

flcPolygonWithX3Y3' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcPolygonWithX3Y3' a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = fromIntegral 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 
  let {a8' = fromIntegral a8} in 
  flcPolygonWithX3Y3''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  return ()

{-# LINE 253 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPolygonWithX3Y3 :: Position -> Int -> Int -> Int -> Int -> Int -> Int ->  IO ()
flcPolygonWithX3Y3 (Position (X x_pos') (Y y_pos')) x1 y1 x2 y2 x3 y3 = flcPolygonWithX3Y3' x_pos' y_pos' x1 y1 x2 y2 x3 y3

flcXyline' :: (Int) -> (Int) -> (Int) -> IO ()
flcXyline' a1 a2 a3 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  flcXyline''_ a1' a2' a3' >>
  return ()

{-# LINE 257 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcXyline :: Position -> Int ->  IO ()
flcXyline (Position (X x_pos') (Y y_pos')) x1 = flcXyline' x_pos' y_pos' x1

flcXylineWithX2' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcXylineWithX2' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcXylineWithX2''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 261 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcXylineWithX2 :: Position -> Int -> Int ->  IO ()
flcXylineWithX2 (Position (X x_pos') (Y y_pos')) x1 y2 = flcXylineWithX2' x_pos' y_pos' x1 y2

flcXylineWithY2X3' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcXylineWithY2X3' a1 a2 a3 a4 a5 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  flcXylineWithY2X3''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 265 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcXylineWithY2X3 :: Position -> Int -> Int -> Int ->  IO ()
flcXylineWithY2X3 (Position (X x_pos') (Y y_pos')) x1 y2 x3 = flcXylineWithY2X3' x_pos' y_pos' x1 y2 x3

flcYxlineWithY1' :: (Int) -> (Int) -> (Int) -> IO ()
flcYxlineWithY1' a1 a2 a3 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  flcYxlineWithY1''_ a1' a2' a3' >>
  return ()

{-# LINE 269 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcYxlineWithY1 :: Position -> Int ->  IO ()
flcYxlineWithY1 (Position (X x_pos') (Y y_pos')) y1 = flcYxlineWithY1' x_pos' y_pos' y1

flcYxlineWithY2X2' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcYxlineWithY2X2' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcYxlineWithY2X2''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 273 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcYxlineWithY2X2 :: Position -> Int -> Int ->  IO ()
flcYxlineWithY2X2 (Position (X x_pos') (Y y_pos')) y1 x2 = flcYxlineWithY2X2' x_pos' y_pos' y1 x2

flcYxlineWithY2X3' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcYxlineWithY2X3' a1 a2 a3 a4 a5 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  flcYxlineWithY2X3''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 277 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcYxlineWithY2X3 :: Position -> Int -> Int -> Int ->  IO ()
flcYxlineWithY2X3 (Position (X x_pos') (Y y_pos')) y1 x2 y3 = flcYxlineWithY2X3' x_pos' y_pos' y1 x2 y3

flcArcByWidthHeight' :: (Int) -> (Int) -> (Int) -> (Int) -> (Double) -> (Double) -> IO ()
flcArcByWidthHeight' a1 a2 a3 a4 a5 a6 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  flcArcByWidthHeight''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 281 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcArcByWidthHeight :: Rectangle -> Double -> Double ->  IO ()
flcArcByWidthHeight rectangle a1 a2 = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcArcByWidthHeight' x_pos' y_pos' width' height' a1 a2

flcPie' :: (Int) -> (Int) -> (Int) -> (Int) -> (Double) -> (Double) -> IO ()
flcPie' a1 a2 a3 a4 a5 a6 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  flcPie''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 285 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPie :: Rectangle -> Double -> Double ->  IO ()
flcPie rectangle a1 a2 = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcPie' x_pos' y_pos' width' height' a1 a2

flcPushMatrix' :: IO ()
flcPushMatrix' =
  flcPushMatrix''_ >>
  return ()

{-# LINE 289 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPushMatrix ::  IO ()
flcPushMatrix  = flcPushMatrix'

flcPopMatrix' :: IO ()
flcPopMatrix' =
  flcPopMatrix''_ >>
  return ()

{-# LINE 293 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcPopMatrix ::  IO ()
flcPopMatrix  = flcPopMatrix'

flcScaleWithY' :: (Double) -> (Double) -> IO ()
flcScaleWithY' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcScaleWithY''_ a1' a2' >>
  return ()

{-# LINE 297 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcScaleWithY :: ByXY ->  IO ()
flcScaleWithY (ByXY (ByX by_x') (ByY by_y')) = flcScaleWithY' by_x' by_y'

flcScale' :: (Double) -> IO ()
flcScale' a1 =
  let {a1' = realToFrac a1} in 
  flcScale''_ a1' >>
  return ()

{-# LINE 301 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcScale :: ByX ->  IO ()
flcScale (ByX by_x') = flcScale' by_x'

flcTranslate' :: (Double) -> (Double) -> IO ()
flcTranslate' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcTranslate''_ a1' a2' >>
  return ()

{-# LINE 305 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTranslate :: ByXY ->  IO ()
flcTranslate (ByXY (ByX by_x') (ByY by_y')) = flcTranslate' by_x' by_y'

flcRotate' :: (Double) -> IO ()
flcRotate' a1 =
  let {a1' = realToFrac a1} in 
  flcRotate''_ a1' >>
  return ()

{-# LINE 309 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRotate :: Double ->  IO ()
flcRotate d = flcRotate' d

flcMultMatrix' :: (Double) -> (Double) -> (Double) -> (Double) -> (Double) -> (Double) -> IO ()
flcMultMatrix' a1 a2 a3 a4 a5 a6 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  flcMultMatrix''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 313 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcMultMatrix :: Double -> Double -> Double -> Double -> ByXY ->  IO ()
flcMultMatrix a b c d (ByXY (ByX by_x') (ByY by_y')) = flcMultMatrix' a b c d by_x' by_y'

flcBeginPoints' :: IO ()
flcBeginPoints' =
  flcBeginPoints''_ >>
  return ()

{-# LINE 317 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcBeginPoints ::  IO ()
flcBeginPoints  = flcBeginPoints'

flcBeginLine' :: IO ()
flcBeginLine' =
  flcBeginLine''_ >>
  return ()

{-# LINE 321 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcBeginLine ::  IO ()
flcBeginLine  = flcBeginLine'

flcBeginLoop' :: IO ()
flcBeginLoop' =
  flcBeginLoop''_ >>
  return ()

{-# LINE 325 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcBeginLoop ::  IO ()
flcBeginLoop  = flcBeginLoop'

flcBeginPolygon' :: IO ()
flcBeginPolygon' =
  flcBeginPolygon''_ >>
  return ()

{-# LINE 329 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcBeginPolygon ::  IO ()
flcBeginPolygon  = flcBeginPolygon'

flcVertex' :: (Double) -> (Double) -> IO ()
flcVertex' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcVertex''_ a1' a2' >>
  return ()

{-# LINE 333 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcVertex :: ByXY ->  IO ()
flcVertex (ByXY (ByX by_x') (ByY by_y')) = flcVertex' by_x' by_y'

flcCurve' :: (Double) -> (Double) -> (Double) -> (Double) -> (Double) -> (Double) -> (Double) -> (Double) -> IO ()
flcCurve' a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  let {a8' = realToFrac a8} in 
  flcCurve''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  return ()

{-# LINE 337 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcCurve :: Double -> Double -> Double -> Double -> Double -> Double -> Double -> Double ->  IO ()
flcCurve x0 y0 x1 y1 x2 y2 x3 y3 = flcCurve' x0 y0 x1 y1 x2 y2 x3 y3

flcArcByRadius' :: (Double) -> (Double) -> (Double) -> (Double) -> (Double) -> IO ()
flcArcByRadius' a1 a2 a3 a4 a5 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  flcArcByRadius''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 341 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcArcByRadius :: ByXY -> Double -> Double -> Double ->  IO ()
flcArcByRadius (ByXY (ByX by_x') (ByY by_y')) r start' end' = flcArcByRadius' by_x' by_y' r start' end'

flcCircle' :: (Double) -> (Double) -> (Double) -> IO ()
flcCircle' a1 a2 a3 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  flcCircle''_ a1' a2' a3' >>
  return ()

{-# LINE 345 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcCircle :: ByXY -> Double ->  IO ()
flcCircle (ByXY (ByX by_x') (ByY by_y')) r = flcCircle' by_x' by_y' r

flcEndPoints' :: IO ()
flcEndPoints' =
  flcEndPoints''_ >>
  return ()

{-# LINE 349 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcEndPoints ::  IO ()
flcEndPoints  = flcEndPoints'

flcEndLine' :: IO ()
flcEndLine' =
  flcEndLine''_ >>
  return ()

{-# LINE 353 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcEndLine ::  IO ()
flcEndLine  = flcEndLine'

flcEndLoop' :: IO ()
flcEndLoop' =
  flcEndLoop''_ >>
  return ()

{-# LINE 357 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcEndLoop ::  IO ()
flcEndLoop  = flcEndLoop'

flcEndPolygon' :: IO ()
flcEndPolygon' =
  flcEndPolygon''_ >>
  return ()

{-# LINE 361 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcEndPolygon ::  IO ()
flcEndPolygon  = flcEndPolygon'

flcBeginComplexPolygon' :: IO ()
flcBeginComplexPolygon' =
  flcBeginComplexPolygon''_ >>
  return ()

{-# LINE 365 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcBeginComplexPolygon ::  IO ()
flcBeginComplexPolygon  = flcBeginComplexPolygon'

flcGap' :: IO ()
flcGap' =
  flcGap''_ >>
  return ()

{-# LINE 369 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcGap ::  IO ()
flcGap  = flcGap'

flcEndComplexPolygon' :: IO ()
flcEndComplexPolygon' =
  flcEndComplexPolygon''_ >>
  return ()

{-# LINE 373 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcEndComplexPolygon ::  IO ()
flcEndComplexPolygon  = flcEndComplexPolygon'

flcTransformX' :: (Double) -> (Double) -> IO ((Double))
flcTransformX' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcTransformX''_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 377 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTransformX :: ByXY ->  IO (Double)
flcTransformX (ByXY (ByX by_x') (ByY by_y')) = flcTransformX' by_x' by_y'

flcTransformY' :: (Double) -> (Double) -> IO ((Double))
flcTransformY' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcTransformY''_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 381 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTransformY :: ByXY ->  IO (Double)
flcTransformY (ByXY (ByX by_x') (ByY by_y')) = flcTransformY' by_x' by_y'

flcTransformDx' :: (Double) -> (Double) -> IO ((Double))
flcTransformDx' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcTransformDx''_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 385 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTransformDx :: ByXY ->  IO (Double)
flcTransformDx (ByXY (ByX by_x') (ByY by_y')) = flcTransformDx' by_x' by_y'

flcTransformDy' :: (Double) -> (Double) -> IO ((Double))
flcTransformDy' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcTransformDy''_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 389 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTransformDy :: ByXY ->  IO (Double)
flcTransformDy (ByXY (ByX by_x') (ByY by_y')) = flcTransformDy' by_x' by_y'

flcTransformedVertex' :: (Double) -> (Double) -> IO ()
flcTransformedVertex' a1 a2 =
  let {a1' = realToFrac a1} in 
  let {a2' = realToFrac a2} in 
  flcTransformedVertex''_ a1' a2' >>
  return ()

{-# LINE 393 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTransformedVertex :: Double -> Double ->  IO ()
flcTransformedVertex xf yf = flcTransformedVertex' xf yf

flcSetFont' :: (Font) -> (CInt) -> IO ()
flcSetFont' a1 a2 =
  let {a1' = cFromFont a1} in 
  let {a2' = id a2} in 
  flcSetFont''_ a1' a2' >>
  return ()

{-# LINE 397 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetFont :: Font -> FontSize ->  IO ()
flcSetFont face (FontSize fsize) = flcSetFont' face fsize

flcFont' :: IO ((Font))
flcFont' =
  flcFont''_ >>= \res ->
  let {res' = cToFont res} in
  return (res')

{-# LINE 401 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcFont ::  IO (Font)
flcFont  = flcFont'

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

{-# LINE 405 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSize ::  IO (FontSize)
flcSize  = flcSize' >>= return . FontSize

flcHeight' :: IO ((Int))
flcHeight' =
  flcHeight''_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 409 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcHeight ::  IO (Int)
flcHeight  = flcHeight'

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

{-# LINE 413 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetHeight :: Int -> Int ->  IO (Int)
flcSetHeight font' size' = flcSetHeight' font' size'

flcDescent' :: IO ((Int))
flcDescent' =
  flcDescent''_ >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 417 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDescent ::  IO (Int)
flcDescent  = flcDescent'

flcWidth' :: (String) -> IO ((Double))
flcWidth' a1 =
  withCString a1 $ \a1' -> 
  flcWidth''_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 421 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcWidth :: String ->  IO (Double)
flcWidth txt = flcWidth' txt

flcWidthWithN' :: (String) -> (Int) -> IO ((Double))
flcWidthWithN' a1 a2 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  flcWidthWithN''_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 425 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcWidthWithN :: String -> Int ->  IO (Double)
flcWidthWithN txt n = flcWidthWithN' txt n

flcWidthWithC' :: (Int) -> IO ((Double))
flcWidthWithC' a1 =
  let {a1' = fromIntegral a1} in 
  flcWidthWithC''_ a1' >>= \res ->
  let {res' = realToFrac res} in
  return (res')

{-# LINE 429 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcWidthWithC :: Int ->  IO (Double)
flcWidthWithC c = flcWidthWithC' c

flcTextExtents' :: (String) -> IO ((Int), (Int), (Int), (Int))
flcTextExtents' a1 =
  withCString a1 $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  alloca $ \a5' -> 
  flcTextExtents''_ a1' a2' a3' a4' a5' >>
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  peekIntConv  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')

{-# LINE 433 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTextExtents :: String -> IO (Rectangle)
flcTextExtents s  = flcTextExtents' s >>= \(rectangle') -> return $ (toRectangle rectangle')

flcTextExtentsWithN' :: (String) -> (Int) -> IO ((Int), (Int), (Int), (Int))
flcTextExtentsWithN' a1 a2 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  alloca $ \a5' -> 
  alloca $ \a6' -> 
  flcTextExtentsWithN''_ a1' a2' a3' a4' a5' a6' >>
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  peekIntConv  a5'>>= \a5'' -> 
  peekIntConv  a6'>>= \a6'' -> 
  return (a3'', a4'', a5'', a6'')

{-# LINE 437 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcTextExtentsWithN :: String -> Int ->  IO (Rectangle)
flcTextExtentsWithN t n  = flcTextExtentsWithN' t n >>= \(rectangle') -> return $ (toRectangle rectangle')

flcLatin1ToLocal' :: (String) -> IO ((String))
flcLatin1ToLocal' a1 =
  withCString a1 $ \a1' -> 
  flcLatin1ToLocal''_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 441 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLatin1ToLocal :: String ->  IO (String)
flcLatin1ToLocal t = flcLatin1ToLocal' t

flcLatin1ToLocalWithN' :: (String) -> (Int) -> IO ((String))
flcLatin1ToLocalWithN' a1 a2 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  flcLatin1ToLocalWithN''_ a1' a2' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 445 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLatin1ToLocalWithN :: String -> Int ->  IO (String)
flcLatin1ToLocalWithN t n = flcLatin1ToLocalWithN' t n

flcLocalToLatin1' :: (String) -> IO ((String))
flcLocalToLatin1' a1 =
  withCString a1 $ \a1' -> 
  flcLocalToLatin1''_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 449 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLocalToLatin1 :: String ->  IO (String)
flcLocalToLatin1 t = flcLocalToLatin1' t

flcLocalToLatin1WithN' :: (String) -> (Int) -> IO ((String))
flcLocalToLatin1WithN' a1 a2 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  flcLocalToLatin1WithN''_ a1' a2' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 453 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLocalToLatin1WithN :: String -> Int ->  IO (String)
flcLocalToLatin1WithN t n = flcLocalToLatin1WithN' t n

flcMacRomanToLocal' :: (String) -> IO ((String))
flcMacRomanToLocal' a1 =
  withCString a1 $ \a1' -> 
  flcMacRomanToLocal''_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 457 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcMacRomanToLocal :: String ->  IO (String)
flcMacRomanToLocal t = flcMacRomanToLocal' t

flcMacRomanToLocalWithN' :: (String) -> (Int) -> IO ((String))
flcMacRomanToLocalWithN' a1 a2 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  flcMacRomanToLocalWithN''_ a1' a2' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 461 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcMacRomanToLocalWithN :: String -> Int ->  IO (String)
flcMacRomanToLocalWithN t n = flcMacRomanToLocalWithN' t n

flcLocalToMacRoman' :: (String) -> IO ((String))
flcLocalToMacRoman' a1 =
  withCString a1 $ \a1' -> 
  flcLocalToMacRoman''_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 465 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLocalToMacRoman :: String ->  IO (String)
flcLocalToMacRoman t = flcLocalToMacRoman' t

flcLocalToMacRomanWithN' :: (String) -> (Int) -> IO ((String))
flcLocalToMacRomanWithN' a1 a2 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  flcLocalToMacRomanWithN''_ a1' a2' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 469 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcLocalToMacRomanWithN :: String -> Int ->  IO (String)
flcLocalToMacRomanWithN t n = flcLocalToMacRomanWithN' t n

flcDraw' :: (String) -> (Int) -> (Int) -> IO ()
flcDraw' a1 a2 a3 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  flcDraw''_ a1' a2' a3' >>
  return ()

{-# LINE 473 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDraw :: String -> Position ->  IO ()
flcDraw str (Position (X x_pos') (Y y_pos')) = flcDraw' str x_pos' y_pos'

flcDrawWithAngle' :: (Int) -> (String) -> (Int) -> (Int) -> IO ()
flcDrawWithAngle' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  withCString a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcDrawWithAngle''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 477 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawWithAngle :: Int -> String -> Position ->  IO ()
flcDrawWithAngle angle str (Position (X x_pos') (Y y_pos')) = flcDrawWithAngle' angle str x_pos' y_pos'

flcDrawWithN' :: (String) -> (Int) -> (Int) -> (Int) -> IO ()
flcDrawWithN' a1 a2 a3 a4 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcDrawWithN''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 481 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawWithN :: String -> Int -> Position ->  IO ()
flcDrawWithN str n (Position (X x_pos') (Y y_pos')) = flcDrawWithN' str n x_pos' y_pos'

flcDrawWithNAngle' :: (Int) -> (String) -> (Int) -> (Int) -> (Int) -> IO ()
flcDrawWithNAngle' a1 a2 a3 a4 a5 =
  let {a1' = fromIntegral a1} in 
  withCString a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  flcDrawWithNAngle''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 485 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawWithNAngle :: Int -> String -> Int -> Position ->  IO ()
flcDrawWithNAngle angle str n (Position (X x_pos') (Y y_pos')) = flcDrawWithNAngle' angle str n x_pos' y_pos'

flcRtlDraw' :: (String) -> (Int) -> (Int) -> (Int) -> IO ()
flcRtlDraw' a1 a2 a3 a4 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcRtlDraw''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 489 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcRtlDraw :: String -> Int -> Position ->  IO ()
flcRtlDraw str n (Position (X x_pos') (Y y_pos')) = flcRtlDraw' str n x_pos' y_pos'

flcMeasureWithDrawSymbols' :: (String) -> (Int) -> IO ((Int), (Int))
flcMeasureWithDrawSymbols' a1 a4 =
  withCString a1 $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  let {a4' = fromIntegral a4} in 
  flcMeasureWithDrawSymbols''_ a1' a2' a3' a4' >>
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  return (a2'', a3'')

{-# LINE 493 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcMeasure :: String -> Maybe Bool -> IO (Size)
flcMeasure str draw_symbols =
    let _draw_symbols = maybe 0 fromBool draw_symbols in
    flcMeasureWithDrawSymbols' str _draw_symbols >>= \(size') -> return $ (toSize size')

flcDrawWithImgDrawSymbols' :: (String) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Ptr ()) -> (Bool) -> IO ()
flcDrawWithImgDrawSymbols' a1 a2 a3 a4 a5 a6 a7 a8 =
  withCString a1 $ \a1' -> 
  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' = id a7} in 
  let {a8' = fromBool a8} in 
  flcDrawWithImgDrawSymbols''_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  return ()

{-# LINE 499 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawWithCallthisImgDrawSymbols' :: (String) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (FunPtr DrawCallbackPrim) -> (Ptr ()) -> (Bool) -> IO ()
flcDrawWithCallthisImgDrawSymbols' a1 a2 a3 a4 a5 a6 a7 a8 a9 =
  withCString a1 $ \a1' -> 
  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' = id a7} in 
  let {a8' = id a8} in 
  let {a9' = fromBool a9} in 
  flcDrawWithCallthisImgDrawSymbols''_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>
  return ()

{-# LINE 500 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawInBoxWithImageReference' ::  String -> Rectangle -> Alignments -> Maybe DrawCallback -> Ptr () -> Maybe Bool -> IO ()
flcDrawInBoxWithImageReference' string' rectangle' align' draw_callback' image_ptr draw_flags' =
  let (x_pos', y_pos', width', height') = fromRectangle rectangle' in
  case draw_callback' of
  Nothing -> flcDrawWithImgDrawSymbols' string' x_pos' y_pos' width' height' (alignmentsToInt align') image_ptr (maybe False id draw_flags')

  Just c' -> do
             fptr <- toDrawCallback c'
             flcDrawWithCallthisImgDrawSymbols' string' x_pos' y_pos' width' height' (alignmentsToInt align') fptr image_ptr (maybe False id draw_flags')
flcDrawInBoxWithImageReference :: (Parent a Image) => String -> Rectangle -> Alignments -> Maybe DrawCallback -> Ref a -> Maybe Bool -> IO ()
flcDrawInBoxWithImageReference string' rectangle' align' draw_callback' image' draw_flags'
  = withRef image' $ \imagePtr' -> flcDrawInBoxWithImageReference' string' rectangle' align' draw_callback' imagePtr' draw_flags'

flcDrawInBox :: String -> Rectangle -> Alignments -> Maybe DrawCallback -> Maybe Bool -> IO ()
flcDrawInBox string' rectangle' align' draw_callback' draw_flags'
  = flcDrawInBoxWithImageReference' string' rectangle' align' draw_callback' (castPtr nullPtr) draw_flags'

flcFrame' :: (String) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcFrame' a1 a2 a3 a4 a5 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  flcFrame''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 518 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcFrame :: String -> Rectangle ->  IO ()
flcFrame s rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcFrame' s x_pos' y_pos' width' height'

flcFrame2' :: (String) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcFrame2' a1 a2 a3 a4 a5 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  flcFrame2''_ a1' a2' a3' a4' a5' >>
  return ()

{-# LINE 522 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcFrame2 :: String -> Rectangle ->  IO ()
flcFrame2 s rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcFrame2' s x_pos' y_pos' width' height'

flcDrawBox' :: (Boxtype) -> (Int) -> (Int) -> (Int) -> (Int) -> (Color) -> IO ()
flcDrawBox' a1 a2 a3 a4 a5 a6 =
  let {a1' = cFromEnum a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = cFromColor a6} in 
  flcDrawBox''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 526 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawBox :: Boxtype -> Rectangle -> Color ->  IO ()
flcDrawBox boxtype rectangle color' = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcDrawBox' boxtype x_pos' y_pos' width' height' color'

flcDrawImageBufWithDL' :: (Ptr CUChar) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcDrawImageBufWithDL' 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 
  flcDrawImageBufWithDL''_ a1' a2' a3' a4' a5' a6' a7' >>
  return ()

{-# LINE 530 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawImageBuf :: ByteString -> Rectangle -> Delta -> LineDelta -> IO ()
flcDrawImageBuf buf rectangle d l =
  let (x_pos', y_pos', width', height') = fromRectangle rectangle
  in unsafeUseAsCString
       buf
       (\cs ->
         case (d,l) of
           (Just d', Nothing) -> flcDrawImageBufWithDL' (castPtr cs) x_pos' y_pos' width' height' d' 0
           (Nothing, Just l') -> flcDrawImageBufWithDL' (castPtr cs) x_pos' y_pos' width' height' 0 l'
           (Nothing, Nothing) -> flcDrawImageBufWithDL' (castPtr cs) x_pos' y_pos' width' height' 0 0
           (Just d', Just l') -> flcDrawImageBufWithDL' (castPtr cs) x_pos' y_pos' width' height' d' l')

flcDrawImageMonoBufWithDL' :: (Ptr CUChar) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcDrawImageMonoBufWithDL' 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 
  flcDrawImageMonoBufWithDL''_ a1' a2' a3' a4' a5' a6' a7' >>
  return ()

{-# LINE 543 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawImageMonoBuf :: ByteString -> Rectangle -> Delta -> LineDelta ->  IO ()
flcDrawImageMonoBuf buf rectangle d l =
  let (x_pos', y_pos', width', height') = fromRectangle rectangle
  in unsafeUseAsCString
       buf
       (\cs ->
         case (d,l) of
           (Just d', Nothing) -> flcDrawImageMonoBufWithDL' (castPtr cs) x_pos' y_pos' width' height' d' 0
           (Nothing, Just l') -> flcDrawImageMonoBufWithDL' (castPtr cs) x_pos' y_pos' width' height' 0 l'
           (Nothing, Nothing) -> flcDrawImageMonoBufWithDL' (castPtr cs) x_pos' y_pos' width' height' 0 0
           (Just d', Just l') -> flcDrawImageMonoBufWithDL' (castPtr cs) x_pos' y_pos' width' height' d' l')

flcCanDoAlphaBlending' :: IO ((Bool))
flcCanDoAlphaBlending' =
  flcCanDoAlphaBlending''_ >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 556 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcCanDoAlphaBlending ::  IO (Bool)
flcCanDoAlphaBlending  = flcCanDoAlphaBlending'

flcReadImageWithAlpha' :: (Ptr CUChar) -> (Int) -> (Int) -> (Int) -> (Int) -> (Bool) -> IO ((Ptr CUChar))
flcReadImageWithAlpha' 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' = fromBool a6} in 
  flcReadImageWithAlpha''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 560 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcReadImage :: Rectangle -> Bool -> IO (ByteString)
flcReadImage rectangle alpha =
  let (x_pos', y_pos', width', height') = fromRectangle rectangle
      buffer_size = width' * height' * (if alpha then 4 else 3)
  in
    do
      buffer <- flcReadImageWithAlpha' nullPtr x_pos' y_pos' width' height' alpha
      bs <- packCStringLen ((castPtr buffer), buffer_size)
      free buffer
      return bs

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

{-# LINE 572 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawPixmapWithColor :: PixmapHs -> Position -> Color ->  IO (Int)
flcDrawPixmapWithColor pixmap (Position (X x_pos') (Y y_pos')) color' =
    withPixmap pixmap $ \pptr -> flcDrawPixmapWithColor' pptr x_pos' y_pos' color'

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

{-# LINE 577 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawPixmap :: PixmapHs -> Position ->  IO (Int)
flcDrawPixmap pixmap (Position (X x_pos') (Y y_pos')) =
    withPixmap pixmap $ \pptr -> flcDrawPixmap' pptr x_pos' y_pos'

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

{-# LINE 582 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawPixmapWithCdataColor :: PixmapHs -> Position -> Color ->  IO (Int)
flcDrawPixmapWithCdataColor pixmap (Position (X x_pos') (Y y_pos')) color' =
    withPixmap pixmap $ \pptr -> flcDrawPixmapWithCdataColor' pptr x_pos' y_pos' color'

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

{-# LINE 587 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawPixmapWithCdata :: PixmapHs -> Position ->  IO (Int)
flcDrawPixmapWithCdata pixmap (Position (X x_pos') (Y y_pos')) =
    withPixmap pixmap $ \pptr -> flcDrawPixmapWithCdata' pptr x_pos' y_pos'

flcMeasurePixmap' :: ((Ptr (Ptr CChar))) -> IO ((Int), (Int), (Int))
flcMeasurePixmap' a1 =
  let {a1' = id a1} in 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  flcMeasurePixmap''_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 592 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcMeasurePixmap :: PixmapHs ->  IO (Int,Size)
flcMeasurePixmap pixmap =
    withPixmap pixmap $ \pptr ->
        flcMeasurePixmap' pptr >>= \(result, width', height') ->
            return $ (result, toSize (width', height'))

flcMeasurePixmapWithCdata' :: ((Ptr (Ptr CChar))) -> IO ((Int), (Int), (Int))
flcMeasurePixmapWithCdata' a1 =
  let {a1' = id a1} in 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  flcMeasurePixmapWithCdata''_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  return (res', a2'', a3'')

{-# LINE 599 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcMeasurePixmapWithCdata :: PixmapHs ->  IO (Int,Size)
flcMeasurePixmapWithCdata pixmap  =
    withPixmap pixmap (\pptr -> do
                         (result, width', height') <- flcMeasurePixmapWithCdata' pptr
                         return (result, toSize (width', height'))
                      )

flcShortcutLabel' :: (Int) -> IO ((String))
flcShortcutLabel' a1 =
  let {a1' = fromIntegral a1} in 
  flcShortcutLabel''_ a1' >>= \res ->
  peekCString res >>= \res' ->
  return (res')

{-# LINE 607 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcShortcutLabel :: Int ->  IO (String)
flcShortcutLabel shortcut = flcShortcutLabel' shortcut

flcOldShortcut' :: (String) -> IO ((Int))
flcOldShortcut' a1 =
  withCString a1 $ \a1' -> 
  flcOldShortcut''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 611 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcOldShortcut :: String -> IO (Int)
flcOldShortcut s = flcOldShortcut' s

flcOverlayRect' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcOverlayRect' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcOverlayRect''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 615 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcOverlayRect :: Rectangle ->  IO ()
flcOverlayRect rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcOverlayRect' x_pos' y_pos' width' height'

flcOverlayClear' :: IO ()
flcOverlayClear' =
  flcOverlayClear''_ >>
  return ()

{-# LINE 619 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcOverlayClear ::  IO ()
flcOverlayClear  = flcOverlayClear'

flcCursorWithFgBg' :: (Cursor) -> (Color) -> (Color) -> IO ()
flcCursorWithFgBg' a1 a2 a3 =
  let {a1' = cFromEnum a1} in 
  let {a2' = cFromColor a2} in 
  let {a3' = cFromColor a3} in 
  flcCursorWithFgBg''_ a1' a2' a3' >>
  return ()

{-# LINE 623 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcCursorWithFgBg :: Cursor -> Color -> Color ->  IO ()
flcCursorWithFgBg cursore fg bg = flcCursorWithFgBg' cursore fg bg

flcCursorWithFg' :: (Cursor) -> (Color) -> IO ()
flcCursorWithFg' a1 a2 =
  let {a1' = cFromEnum a1} in 
  let {a2' = cFromColor a2} in 
  flcCursorWithFg''_ a1' a2' >>
  return ()

{-# LINE 627 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcCursorWithFg :: Cursor -> Color ->  IO ()
flcCursorWithFg cursor fg = flcCursorWithFg' cursor fg

flcCursorWithBg' :: (Cursor) -> (Color) -> IO ()
flcCursorWithBg' a1 a2 =
  let {a1' = cFromEnum a1} in 
  let {a2' = cFromColor a2} in 
  flcCursorWithBg''_ a1' a2' >>
  return ()

{-# LINE 631 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcCursorWithBg :: Cursor -> Color ->  IO ()
flcCursorWithBg cursor bg = flcCursorWithBg' cursor bg

flcCursor' :: (Cursor) -> IO ()
flcCursor' a1 =
  let {a1' = cFromEnum a1} in 
  flcCursor''_ a1' >>
  return ()

{-# LINE 635 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcCursor :: Cursor ->  IO ()
flcCursor cursor = flcCursor' cursor

flcSetStatus' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcSetStatus' a1 a2 a3 a4 =
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  flcSetStatus''_ a1' a2' a3' a4' >>
  return ()

{-# LINE 639 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetStatus :: Rectangle ->  IO ()
flcSetStatus rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcSetStatus' x_pos' y_pos' width' height'

flcSetSpotWithWin' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Ptr ()) -> IO ()
flcSetSpotWithWin' a1 a2 a3 a4 a5 a6 a7 =
  let {a1' = fromIntegral 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' = id a7} in 
  flcSetSpotWithWin''_ a1' a2' a3' a4' a5' a6' a7' >>
  return ()

{-# LINE 643 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetSpotWithWin :: (Parent a Window) => Int -> Int -> Rectangle -> Ref a -> IO ()
flcSetSpotWithWin font' size' rectangle win = let (x_pos', y_pos', width', height') = fromRectangle rectangle in withRef win $ \winPtr -> flcSetSpotWithWin' font' size' x_pos' y_pos' width' height' winPtr

flcSetSpot' :: (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ()
flcSetSpot' a1 a2 a3 a4 a5 a6 =
  let {a1' = fromIntegral 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 
  flcSetSpot''_ a1' a2' a3' a4' a5' a6' >>
  return ()

{-# LINE 647 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcSetSpot :: Int -> Int -> Rectangle ->  IO ()
flcSetSpot font' size' rectangle = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcSetSpot' font' size' x_pos' y_pos' width' height'

flcResetSpot' :: IO ()
flcResetSpot' =
  flcResetSpot''_ >>
  return ()

{-# LINE 651 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcResetSpot ::  IO ()
flcResetSpot  = flcResetSpot'

flcDrawSymbol' :: (String) -> (Int) -> (Int) -> (Int) -> (Int) -> (Color) -> IO ((Int))
flcDrawSymbol' a1 a2 a3 a4 a5 a6 =
  withCString a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  let {a6' = cFromColor a6} in 
  flcDrawSymbol''_ a1' a2' a3' a4' a5' a6' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 655 "src/Graphics/UI/FLTK/LowLevel/Draw.chs" #-}

flcDrawSymbol :: String -> Rectangle -> Color ->  IO (Int)
flcDrawSymbol label rectangle color' = let (x_pos', y_pos', width', height') = fromRectangle rectangle in flcDrawSymbol' label x_pos' y_pos' width' height' color'

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_color"
  flcSetColor''_ :: (CUInt -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_color_with_c"
  flcSetColorWithC''_ :: (CInt -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_color_with_rgb"
  flcSetColorWithRgb''_ :: (CUChar -> (CUChar -> (CUChar -> (IO ()))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_color"
  flcColor''_ :: (IO CUInt)

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_push_clip"
  flcPushClip''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_push_no_clip"
  flcPushNoClip''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_pop_clip"
  flcPopClip''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_not_clipped"
  flcNotClipped''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO CInt)))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_clip_box"
  flcClipBox''_ :: (CInt -> (CInt -> (CInt -> (CInt -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO CInt)))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_restore_clip"
  flcRestoreClip''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_clip_region"
  flcSetClipRegion''_ :: ((Ptr ()) -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_clip_region"
  flcClipRegion''_ :: (IO (Ptr ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_point"
  flcPoint''_ :: (CInt -> (CInt -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_line_style_with_width_dashes"
  flcLineStyleWithWidthDashes''_ :: (CInt -> (CInt -> ((Ptr CChar) -> (IO ()))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_rect"
  flcRect''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_rect_with_color"
  flcRectWithColor''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_rectf"
  flcRectf''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_rectf_with_color"
  flcRectfWithColor''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_rectf_with_rgb"
  flcRectfWithRgb''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CUChar -> (CUChar -> (CUChar -> (IO ()))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_line"
  flcLine''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_line_with_x2_y2"
  flcLineWithX2Y2''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_loop"
  flcLoop''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_loop_with_x3_y3"
  flcLoopWithX3Y3''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_polygon"
  flcPolygon''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_polygon_with_x3_y3"
  flcPolygonWithX3Y3''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_xyline"
  flcXyline''_ :: (CInt -> (CInt -> (CInt -> (IO ()))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_xyline_with_x2"
  flcXylineWithX2''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_xyline_with_y2_x3"
  flcXylineWithY2X3''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_yxline_with_y1"
  flcYxlineWithY1''_ :: (CInt -> (CInt -> (CInt -> (IO ()))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_yxline_with_y2_x2"
  flcYxlineWithY2X2''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_yxline_with_y2_x3"
  flcYxlineWithY2X3''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_arc_by_width_height"
  flcArcByWidthHeight''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CDouble -> (CDouble -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_pie"
  flcPie''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CDouble -> (CDouble -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_push_matrix"
  flcPushMatrix''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_pop_matrix"
  flcPopMatrix''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_scale_with_y"
  flcScaleWithY''_ :: (CDouble -> (CDouble -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_scale"
  flcScale''_ :: (CDouble -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_translate"
  flcTranslate''_ :: (CDouble -> (CDouble -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_rotate"
  flcRotate''_ :: (CDouble -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_mult_matrix"
  flcMultMatrix''_ :: (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_begin_points"
  flcBeginPoints''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_begin_line"
  flcBeginLine''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_begin_loop"
  flcBeginLoop''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_begin_polygon"
  flcBeginPolygon''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_vertex"
  flcVertex''_ :: (CDouble -> (CDouble -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_curve"
  flcCurve''_ :: (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (IO ())))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_arc_by_radius"
  flcArcByRadius''_ :: (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_circle"
  flcCircle''_ :: (CDouble -> (CDouble -> (CDouble -> (IO ()))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_end_points"
  flcEndPoints''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_end_line"
  flcEndLine''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_end_loop"
  flcEndLoop''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_end_polygon"
  flcEndPolygon''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_begin_complex_polygon"
  flcBeginComplexPolygon''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_gap"
  flcGap''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_end_complex_polygon"
  flcEndComplexPolygon''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_transform_x"
  flcTransformX''_ :: (CDouble -> (CDouble -> (IO CDouble)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_transform_y"
  flcTransformY''_ :: (CDouble -> (CDouble -> (IO CDouble)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_transform_dx"
  flcTransformDx''_ :: (CDouble -> (CDouble -> (IO CDouble)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_transform_dy"
  flcTransformDy''_ :: (CDouble -> (CDouble -> (IO CDouble)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_transformed_vertex"
  flcTransformedVertex''_ :: (CDouble -> (CDouble -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_font"
  flcSetFont''_ :: (CInt -> (CInt -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_font"
  flcFont''_ :: (IO CInt)

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_size"
  flcSize''_ :: (IO CInt)

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_height"
  flcHeight''_ :: (IO CInt)

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_height"
  flcSetHeight''_ :: (CInt -> (CInt -> (IO CInt)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_descent"
  flcDescent''_ :: (IO CInt)

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_width"
  flcWidth''_ :: ((Ptr CChar) -> (IO CDouble))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_width_with_n"
  flcWidthWithN''_ :: ((Ptr CChar) -> (CInt -> (IO CDouble)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_width_with_c"
  flcWidthWithC''_ :: (CUInt -> (IO CDouble))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_text_extents"
  flcTextExtents''_ :: ((Ptr CChar) -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_text_extents_with_n"
  flcTextExtentsWithN''_ :: ((Ptr CChar) -> (CInt -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_latin1_to_local"
  flcLatin1ToLocal''_ :: ((Ptr CChar) -> (IO (Ptr CChar)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_latin1_to_local_with_n"
  flcLatin1ToLocalWithN''_ :: ((Ptr CChar) -> (CInt -> (IO (Ptr CChar))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_local_to_latin1"
  flcLocalToLatin1''_ :: ((Ptr CChar) -> (IO (Ptr CChar)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_local_to_latin1_with_n"
  flcLocalToLatin1WithN''_ :: ((Ptr CChar) -> (CInt -> (IO (Ptr CChar))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_mac_roman_to_local"
  flcMacRomanToLocal''_ :: ((Ptr CChar) -> (IO (Ptr CChar)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_mac_roman_to_local_with_n"
  flcMacRomanToLocalWithN''_ :: ((Ptr CChar) -> (CInt -> (IO (Ptr CChar))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_local_to_mac_roman"
  flcLocalToMacRoman''_ :: ((Ptr CChar) -> (IO (Ptr CChar)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_local_to_mac_roman_with_n"
  flcLocalToMacRomanWithN''_ :: ((Ptr CChar) -> (CInt -> (IO (Ptr CChar))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw"
  flcDraw''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (IO ()))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_with_angle"
  flcDrawWithAngle''_ :: (CInt -> ((Ptr CChar) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_with_n"
  flcDrawWithN''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_with_n_angle"
  flcDrawWithNAngle''_ :: (CInt -> ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_rtl_draw"
  flcRtlDraw''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_measure_with_draw_symbols"
  flcMeasureWithDrawSymbols''_ :: ((Ptr CChar) -> ((Ptr CInt) -> ((Ptr CInt) -> (CInt -> (IO ())))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_with_img_draw_symbols"
  flcDrawWithImgDrawSymbols''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> ((Ptr ()) -> (CInt -> (IO ())))))))))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_with_callthis_img_draw_symbols"
  flcDrawWithCallthisImgDrawSymbols''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> ((FunPtr ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (IO ())))))) -> ((Ptr ()) -> (CInt -> (IO ()))))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_frame"
  flcFrame''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_frame2"
  flcFrame2''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_box"
  flcDrawBox''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_image_buf_with_d_l"
  flcDrawImageBufWithDL''_ :: ((Ptr CUChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_image_mono_buf_with_d_l"
  flcDrawImageMonoBufWithDL''_ :: ((Ptr CUChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_can_do_alpha_blending"
  flcCanDoAlphaBlending''_ :: (IO CChar)

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_read_image_with_alpha"
  flcReadImageWithAlpha''_ :: ((Ptr CUChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO (Ptr CUChar))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_pixmap_with_color"
  flcDrawPixmapWithColor''_ :: ((Ptr (Ptr CChar)) -> (CInt -> (CInt -> (CUInt -> (IO CInt)))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_pixmap"
  flcDrawPixmap''_ :: ((Ptr (Ptr CChar)) -> (CInt -> (CInt -> (IO CInt))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_pixmap_with_cdata_color"
  flcDrawPixmapWithCdataColor''_ :: ((Ptr (Ptr CChar)) -> (CInt -> (CInt -> (CUInt -> (IO CInt)))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_pixmap_with_cdata"
  flcDrawPixmapWithCdata''_ :: ((Ptr (Ptr CChar)) -> (CInt -> (CInt -> (IO CInt))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_measure_pixmap"
  flcMeasurePixmap''_ :: ((Ptr (Ptr CChar)) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO CInt))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_measure_pixmap_with_cdata"
  flcMeasurePixmapWithCdata''_ :: ((Ptr (Ptr CChar)) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO CInt))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_shortcut_label"
  flcShortcutLabel''_ :: (CUInt -> (IO (Ptr CChar)))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_old_shortcut"
  flcOldShortcut''_ :: ((Ptr CChar) -> (IO CUInt))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_overlay_rect"
  flcOverlayRect''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_overlay_clear"
  flcOverlayClear''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_cursor_with_fg_bg"
  flcCursorWithFgBg''_ :: (CInt -> (CUInt -> (CUInt -> (IO ()))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_cursor_with_fg"
  flcCursorWithFg''_ :: (CInt -> (CUInt -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_cursor_with_bg"
  flcCursorWithBg''_ :: (CInt -> (CUInt -> (IO ())))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_cursor"
  flcCursor''_ :: (CInt -> (IO ()))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_status"
  flcSetStatus''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_spot_with_win"
  flcSetSpotWithWin''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> ((Ptr ()) -> (IO ()))))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_set_spot"
  flcSetSpot''_ :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ())))))))

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_reset_spot"
  flcResetSpot''_ :: (IO ())

foreign import ccall unsafe "Graphics/UI/FLTK/LowLevel/Draw.chs.h flc_draw_symbol"
  flcDrawSymbol''_ :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CUInt -> (IO CInt)))))))