{-# LINE 1 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
module Graphics.Rendering.Cairo.Internal.Region where
import Graphics.Rendering.Cairo.Types
{-# LINE 18 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
import Foreign
import Foreign.C
{-# LINE 23 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionCreateRectangles rects =
withArrayLen rects $ \ n ptr ->
cairo_region_create_rectangles ptr (fromIntegral n) >>= mkRegion
regionCreate :: IO (Region)
regionCreate =
regionCreate'_ >>= \res ->
mkRegion res >>= \res' ->
return (res')
{-# LINE 29 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionCreateRectangle :: RectangleInt -> IO (Region)
regionCreateRectangle a1 =
with a1 $ \a1' ->
regionCreateRectangle'_ a1' >>= \res ->
mkRegion res >>= \res' ->
return (res')
{-# LINE 30 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionCopy :: Region -> IO (Region)
regionCopy a1 =
withRegion a1 $ \a1' ->
regionCopy'_ a1' >>= \res ->
mkRegion res >>= \res' ->
return (res')
{-# LINE 31 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionDestroy :: Region -> IO ()
regionDestroy a1 =
withRegion a1 $ \a1' ->
regionDestroy'_ a1' >>= \res ->
return ()
{-# LINE 32 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionReference :: Region -> IO ()
regionReference a1 =
withRegion a1 $ \a1' ->
regionReference'_ a1' >>= \res ->
return ()
{-# LINE 33 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionStatus :: Region -> IO (Status)
regionStatus a1 =
withRegion a1 $ \a1' ->
regionStatus'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 34 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionGetExtents :: Region -> IO (RectangleInt)
regionGetExtents a1 =
withRegion a1 $ \a1' ->
alloca $ \a2' ->
regionGetExtents'_ a1' a2' >>= \res ->
peek a2'>>= \a2'' ->
return (a2'')
{-# LINE 35 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionNumRectangles :: Region -> IO (Int)
regionNumRectangles a1 =
withRegion a1 $ \a1' ->
regionNumRectangles'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 36 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionGetRectangle :: Region -> Int -> IO (RectangleInt)
regionGetRectangle a1 a2 =
withRegion a1 $ \a1' ->
let {a2' = fromIntegral a2} in
alloca $ \a3' ->
regionGetRectangle'_ a1' a2' a3' >>= \res ->
peek a3'>>= \a3'' ->
return (a3'')
{-# LINE 37 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionIsEmpty :: Region -> IO (Bool)
regionIsEmpty a1 =
withRegion a1 $ \a1' ->
regionIsEmpty'_ a1' >>= \res ->
let {res' = cToBool res} in
return (res')
{-# LINE 38 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionContainsPoint :: Region -> Int -> Int -> IO (Bool)
regionContainsPoint a1 a2 a3 =
withRegion a1 $ \a1' ->
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
regionContainsPoint'_ a1' a2' a3' >>= \res ->
let {res' = cToBool res} in
return (res')
{-# LINE 39 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionContainsRectangle :: Region -> RectangleInt -> IO (RegionOverlap)
regionContainsRectangle a1 a2 =
withRegion a1 $ \a1' ->
with a2 $ \a2' ->
regionContainsRectangle'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 40 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionEqual :: Region -> Region -> IO (Bool)
regionEqual a1 a2 =
withRegion a1 $ \a1' ->
withRegion a2 $ \a2' ->
regionEqual'_ a1' a2' >>= \res ->
let {res' = cToBool res} in
return (res')
{-# LINE 41 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionTranslate :: Region -> Int -> Int -> IO ()
regionTranslate a1 a2 a3 =
withRegion a1 $ \a1' ->
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
regionTranslate'_ a1' a2' a3' >>= \res ->
return ()
{-# LINE 42 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionIntersect :: Region -> Region -> IO (Status)
regionIntersect a1 a2 =
withRegion a1 $ \a1' ->
withRegion a2 $ \a2' ->
regionIntersect'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 43 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionIntersectRectangle :: Region -> RectangleInt -> IO (Status)
regionIntersectRectangle a1 a2 =
withRegion a1 $ \a1' ->
with a2 $ \a2' ->
regionIntersectRectangle'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 44 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionSubtract :: Region -> Region -> IO (Status)
regionSubtract a1 a2 =
withRegion a1 $ \a1' ->
withRegion a2 $ \a2' ->
regionSubtract'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 45 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionSubtractRectangle :: Region -> RectangleInt -> IO (Status)
regionSubtractRectangle a1 a2 =
withRegion a1 $ \a1' ->
with a2 $ \a2' ->
regionSubtractRectangle'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 46 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionUnion :: Region -> Region -> IO (Status)
regionUnion a1 a2 =
withRegion a1 $ \a1' ->
withRegion a2 $ \a2' ->
regionUnion'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 47 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionUnionRectangle :: Region -> RectangleInt -> IO (Status)
regionUnionRectangle a1 a2 =
withRegion a1 $ \a1' ->
with a2 $ \a2' ->
regionUnionRectangle'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 48 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionXor :: Region -> Region -> IO (Status)
regionXor a1 a2 =
withRegion a1 $ \a1' ->
withRegion a2 $ \a2' ->
regionXor'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 49 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
regionXorRectangle :: Region -> RectangleInt -> IO (Status)
regionXorRectangle a1 a2 =
withRegion a1 $ \a1' ->
with a2 $ \a2' ->
regionXorRectangle'_ a1' a2' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 50 "./Graphics/Rendering/Cairo/Internal/Region.chs" #-}
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_create_rectangles"
cairo_region_create_rectangles :: ((Ptr RectangleInt) -> (CInt -> (IO (Ptr Region))))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_create"
regionCreate'_ :: (IO (Ptr Region))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_create_rectangle"
regionCreateRectangle'_ :: ((Ptr RectangleInt) -> (IO (Ptr Region)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_copy"
regionCopy'_ :: ((Ptr Region) -> (IO (Ptr Region)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_destroy"
regionDestroy'_ :: ((Ptr Region) -> (IO ()))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_reference"
regionReference'_ :: ((Ptr Region) -> (IO (Ptr Region)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_status"
regionStatus'_ :: ((Ptr Region) -> (IO CInt))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_get_extents"
regionGetExtents'_ :: ((Ptr Region) -> ((Ptr RectangleInt) -> (IO ())))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_num_rectangles"
regionNumRectangles'_ :: ((Ptr Region) -> (IO CInt))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_get_rectangle"
regionGetRectangle'_ :: ((Ptr Region) -> (CInt -> ((Ptr RectangleInt) -> (IO ()))))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_is_empty"
regionIsEmpty'_ :: ((Ptr Region) -> (IO CInt))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_contains_point"
regionContainsPoint'_ :: ((Ptr Region) -> (CInt -> (CInt -> (IO CInt))))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_contains_rectangle"
regionContainsRectangle'_ :: ((Ptr Region) -> ((Ptr RectangleInt) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_equal"
regionEqual'_ :: ((Ptr Region) -> ((Ptr Region) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_translate"
regionTranslate'_ :: ((Ptr Region) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_intersect"
regionIntersect'_ :: ((Ptr Region) -> ((Ptr Region) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_intersect_rectangle"
regionIntersectRectangle'_ :: ((Ptr Region) -> ((Ptr RectangleInt) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_subtract"
regionSubtract'_ :: ((Ptr Region) -> ((Ptr Region) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_subtract_rectangle"
regionSubtractRectangle'_ :: ((Ptr Region) -> ((Ptr RectangleInt) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_union"
regionUnion'_ :: ((Ptr Region) -> ((Ptr Region) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_union_rectangle"
regionUnionRectangle'_ :: ((Ptr Region) -> ((Ptr RectangleInt) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_xor"
regionXor'_ :: ((Ptr Region) -> ((Ptr Region) -> (IO CInt)))
foreign import ccall safe "dist-docs.QiueOM/build/Graphics/Rendering/Cairo/Internal/Region.h cairo_region_xor_rectangle"
regionXorRectangle'_ :: ((Ptr Region) -> ((Ptr RectangleInt) -> (IO CInt)))