#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.PangoCairo.Callbacks
(
C_ShapeRendererFunc ,
ShapeRendererFunc ,
dynamic_ShapeRendererFunc ,
genClosure_ShapeRendererFunc ,
mk_ShapeRendererFunc ,
noShapeRendererFunc ,
wrap_ShapeRendererFunc ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Pango.Structs.AttrShape as Pango.AttrShape
type C_ShapeRendererFunc =
Ptr Cairo.Context.Context ->
Ptr Pango.AttrShape.AttrShape ->
CInt ->
Ptr () ->
IO ()
foreign import ccall "dynamic" __dynamic_C_ShapeRendererFunc :: FunPtr C_ShapeRendererFunc -> C_ShapeRendererFunc
dynamic_ShapeRendererFunc ::
(B.CallStack.HasCallStack, MonadIO m) =>
FunPtr C_ShapeRendererFunc
-> Cairo.Context.Context
-> Pango.AttrShape.AttrShape
-> Bool
-> Ptr ()
-> m ()
dynamic_ShapeRendererFunc :: FunPtr C_ShapeRendererFunc
-> Context -> AttrShape -> Bool -> Ptr () -> m ()
dynamic_ShapeRendererFunc __funPtr :: FunPtr C_ShapeRendererFunc
__funPtr cr :: Context
cr attr :: AttrShape
attr doPath :: Bool
doPath data_ :: Ptr ()
data_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Context
cr' <- Context -> IO (Ptr Context)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Context
cr
Ptr AttrShape
attr' <- AttrShape -> IO (Ptr AttrShape)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrShape
attr
let doPath' :: CInt
doPath' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
doPath
(FunPtr C_ShapeRendererFunc -> C_ShapeRendererFunc
__dynamic_C_ShapeRendererFunc FunPtr C_ShapeRendererFunc
__funPtr) Ptr Context
cr' Ptr AttrShape
attr' CInt
doPath' Ptr ()
data_
Context -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Context
cr
AttrShape -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrShape
attr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
foreign import ccall "wrapper"
mk_ShapeRendererFunc :: C_ShapeRendererFunc -> IO (FunPtr C_ShapeRendererFunc)
type ShapeRendererFunc =
Cairo.Context.Context
-> Pango.AttrShape.AttrShape
-> Bool
-> Ptr ()
-> IO ()
noShapeRendererFunc :: Maybe ShapeRendererFunc
noShapeRendererFunc :: Maybe ShapeRendererFunc
noShapeRendererFunc = Maybe ShapeRendererFunc
forall a. Maybe a
Nothing
genClosure_ShapeRendererFunc :: MonadIO m => ShapeRendererFunc -> m (GClosure C_ShapeRendererFunc)
genClosure_ShapeRendererFunc :: ShapeRendererFunc -> m (GClosure C_ShapeRendererFunc)
genClosure_ShapeRendererFunc cb :: ShapeRendererFunc
cb = IO (GClosure C_ShapeRendererFunc)
-> m (GClosure C_ShapeRendererFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ShapeRendererFunc)
-> m (GClosure C_ShapeRendererFunc))
-> IO (GClosure C_ShapeRendererFunc)
-> m (GClosure C_ShapeRendererFunc)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ShapeRendererFunc
cb' = Maybe (Ptr (FunPtr C_ShapeRendererFunc))
-> ShapeRendererFunc -> C_ShapeRendererFunc
wrap_ShapeRendererFunc Maybe (Ptr (FunPtr C_ShapeRendererFunc))
forall a. Maybe a
Nothing ShapeRendererFunc
cb
C_ShapeRendererFunc -> IO (FunPtr C_ShapeRendererFunc)
mk_ShapeRendererFunc C_ShapeRendererFunc
cb' IO (FunPtr C_ShapeRendererFunc)
-> (FunPtr C_ShapeRendererFunc
-> IO (GClosure C_ShapeRendererFunc))
-> IO (GClosure C_ShapeRendererFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ShapeRendererFunc -> IO (GClosure C_ShapeRendererFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ShapeRendererFunc ::
Maybe (Ptr (FunPtr C_ShapeRendererFunc)) ->
ShapeRendererFunc ->
C_ShapeRendererFunc
wrap_ShapeRendererFunc :: Maybe (Ptr (FunPtr C_ShapeRendererFunc))
-> ShapeRendererFunc -> C_ShapeRendererFunc
wrap_ShapeRendererFunc funptrptr :: Maybe (Ptr (FunPtr C_ShapeRendererFunc))
funptrptr _cb :: ShapeRendererFunc
_cb cr :: Ptr Context
cr attr :: Ptr AttrShape
attr doPath :: CInt
doPath data_ :: Ptr ()
data_ = do
(ManagedPtr Context -> Context)
-> Ptr Context -> (Context -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr Context -> Context
Cairo.Context.Context Ptr Context
cr ((Context -> IO ()) -> IO ()) -> (Context -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \cr' :: Context
cr' -> do
AttrShape
attr' <- ((ManagedPtr AttrShape -> AttrShape)
-> Ptr AttrShape -> IO AttrShape
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr AttrShape -> AttrShape
Pango.AttrShape.AttrShape) Ptr AttrShape
attr
let doPath' :: Bool
doPath' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
doPath
ShapeRendererFunc
_cb Context
cr' AttrShape
attr' Bool
doPath' Ptr ()
data_
Maybe (Ptr (FunPtr C_ShapeRendererFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_ShapeRendererFunc))
funptrptr