{-# LINE 1 "src/Graphics/Cairo/Utilities/Types.hsc" #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE BlockArguments, TupleSections #-} {-# LANGUAGE PatternSynonyms, ViewPatterns #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Graphics.Cairo.Utilities.Types where import Foreign.Ptr import Foreign.Concurrent import Foreign.Marshal import Foreign.Storable import Foreign.C.Types import Foreign.C.Struct import Control.Monad.Primitive struct "CairoRectangleIntT" (16) {-# LINE 19 "src/Graphics/Cairo/Utilities/Types.hsc" #-} 4 {-# LINE 20 "src/Graphics/Cairo/Utilities/Types.hsc" #-} [ ("x", ''CInt, [| (\hsc_ptr -> peekByteOff hsc_ptr 0) |], {-# LINE 21 "src/Graphics/Cairo/Utilities/Types.hsc" #-} [| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]), {-# LINE 22 "src/Graphics/Cairo/Utilities/Types.hsc" #-} ("y", ''CInt, [| (\hsc_ptr -> peekByteOff hsc_ptr 4) |], {-# LINE 23 "src/Graphics/Cairo/Utilities/Types.hsc" #-} [| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]), {-# LINE 24 "src/Graphics/Cairo/Utilities/Types.hsc" #-} ("width", ''CInt, [| (\hsc_ptr -> peekByteOff hsc_ptr 8) |], {-# LINE 25 "src/Graphics/Cairo/Utilities/Types.hsc" #-} [| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]), {-# LINE 26 "src/Graphics/Cairo/Utilities/Types.hsc" #-} ("height", ''CInt, [| (\hsc_ptr -> peekByteOff hsc_ptr 12) |], {-# LINE 27 "src/Graphics/Cairo/Utilities/Types.hsc" #-} [| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]) ] {-# LINE 28 "src/Graphics/Cairo/Utilities/Types.hsc" #-} [''Show] c_cairo_rectangle_int_t_copy :: Ptr CairoRectangleIntT -> IO (Ptr CairoRectangleIntT) c_cairo_rectangle_int_t_copy :: Ptr CairoRectangleIntT -> IO (Ptr CairoRectangleIntT) c_cairo_rectangle_int_t_copy Ptr CairoRectangleIntT s = do d <- Int -> IO (Ptr CairoRectangleIntT) forall a. Int -> IO (Ptr a) mallocBytes (Int 16) {-# LINE 34 "src/Graphics/Cairo/Utilities/Types.hsc" #-} d <$ copyBytes d s (16) {-# LINE 35 "src/Graphics/Cairo/Utilities/Types.hsc" #-} c_cairo_rectangle_int_t_free :: Ptr CairoRectangleIntT -> IO () c_cairo_rectangle_int_t_free :: Ptr CairoRectangleIntT -> IO () c_cairo_rectangle_int_t_free = Ptr CairoRectangleIntT -> IO () forall a. Ptr a -> IO () free structPrim "CairoRectangleIntT" 'c_cairo_rectangle_int_t_copy 'c_cairo_rectangle_int_t_free [''Show] cairoRectangleIntTNew :: PrimMonad m => m (CairoRectangleIntTPrim (PrimState m)) cairoRectangleIntTNew :: forall (m :: * -> *). PrimMonad m => m (CairoRectangleIntTPrim (PrimState m)) cairoRectangleIntTNew = ForeignPtr CairoRectangleIntT -> CairoRectangleIntTPrim (PrimState m) forall s. ForeignPtr CairoRectangleIntT -> CairoRectangleIntTPrim s CairoRectangleIntTPrim (ForeignPtr CairoRectangleIntT -> CairoRectangleIntTPrim (PrimState m)) -> m (ForeignPtr CairoRectangleIntT) -> m (CairoRectangleIntTPrim (PrimState m)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> IO (ForeignPtr CairoRectangleIntT) -> m (ForeignPtr CairoRectangleIntT) forall (m :: * -> *) a. PrimMonad m => IO a -> m a unsafeIOToPrim do p <- Int -> IO (Ptr CairoRectangleIntT) forall a. Int -> IO (Ptr a) mallocBytes (Int 16) {-# LINE 45 "src/Graphics/Cairo/Utilities/Types.hsc" #-} newForeignPtr p $ free p