#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gsk.Callbacks
(
C_ParseErrorFunc ,
ParseErrorFunc ,
ParseErrorFunc_WithClosures ,
drop_closures_ParseErrorFunc ,
dynamic_ParseErrorFunc ,
genClosure_ParseErrorFunc ,
mk_ParseErrorFunc ,
noParseErrorFunc ,
noParseErrorFunc_WithClosures ,
wrap_ParseErrorFunc ,
C_PathForeachFunc ,
PathForeachFunc ,
PathForeachFunc_WithClosures ,
drop_closures_PathForeachFunc ,
dynamic_PathForeachFunc ,
genClosure_PathForeachFunc ,
mk_PathForeachFunc ,
noPathForeachFunc ,
noPathForeachFunc_WithClosures ,
wrap_PathForeachFunc ,
) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Graphene.Structs.Point as Graphene.Point
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
import {-# SOURCE #-} qualified GI.Gsk.Structs.ParseLocation as Gsk.ParseLocation
#else
import qualified GI.Graphene.Structs.Point as Graphene.Point
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
import {-# SOURCE #-} qualified GI.Gsk.Structs.ParseLocation as Gsk.ParseLocation
#endif
type C_PathForeachFunc =
CUInt ->
Ptr Graphene.Point.Point ->
FCT.CSize ->
CFloat ->
Ptr () ->
IO CInt
foreign import ccall "dynamic" __dynamic_C_PathForeachFunc :: FunPtr C_PathForeachFunc -> C_PathForeachFunc
dynamic_PathForeachFunc ::
(B.CallStack.HasCallStack, MonadIO m) =>
FunPtr C_PathForeachFunc
-> Gsk.Enums.PathOperation
-> Graphene.Point.Point
-> FCT.CSize
-> Float
-> Ptr ()
-> m Bool
dynamic_PathForeachFunc :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_PathForeachFunc
-> PathOperation -> Point -> CSize -> Float -> Ptr () -> m Bool
dynamic_PathForeachFunc FunPtr C_PathForeachFunc
__funPtr PathOperation
op Point
pts CSize
nPts Float
weight Ptr ()
userData = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
let op' :: CUInt
op' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PathOperation -> Int) -> PathOperation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PathOperation -> Int
forall a. Enum a => a -> Int
fromEnum) PathOperation
op
Ptr Point
pts' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
pts
let weight' :: CFloat
weight' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
weight
CInt
result <- (FunPtr C_PathForeachFunc -> C_PathForeachFunc
__dynamic_C_PathForeachFunc FunPtr C_PathForeachFunc
__funPtr) CUInt
op' Ptr Point
pts' CSize
nPts CFloat
weight' Ptr ()
userData
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
pts
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
foreign import ccall "wrapper"
mk_PathForeachFunc :: C_PathForeachFunc -> IO (FunPtr C_PathForeachFunc)
type PathForeachFunc =
Gsk.Enums.PathOperation
-> Graphene.Point.Point
-> FCT.CSize
-> Float
-> IO Bool
noPathForeachFunc :: Maybe PathForeachFunc
noPathForeachFunc :: Maybe PathForeachFunc
noPathForeachFunc = Maybe PathForeachFunc
forall a. Maybe a
Nothing
type PathForeachFunc_WithClosures =
Gsk.Enums.PathOperation
-> Graphene.Point.Point
-> FCT.CSize
-> Float
-> Ptr ()
-> IO Bool
noPathForeachFunc_WithClosures :: Maybe PathForeachFunc_WithClosures
noPathForeachFunc_WithClosures :: Maybe PathForeachFunc_WithClosures
noPathForeachFunc_WithClosures = Maybe PathForeachFunc_WithClosures
forall a. Maybe a
Nothing
drop_closures_PathForeachFunc :: PathForeachFunc -> PathForeachFunc_WithClosures
drop_closures_PathForeachFunc :: PathForeachFunc -> PathForeachFunc_WithClosures
drop_closures_PathForeachFunc PathForeachFunc
_f PathOperation
op Point
pts CSize
nPts Float
weight Ptr ()
_ = PathForeachFunc
_f PathOperation
op Point
pts CSize
nPts Float
weight
genClosure_PathForeachFunc :: MonadIO m => PathForeachFunc -> m (GClosure C_PathForeachFunc)
genClosure_PathForeachFunc :: forall (m :: * -> *).
MonadIO m =>
PathForeachFunc -> m (GClosure C_PathForeachFunc)
genClosure_PathForeachFunc PathForeachFunc
cb = IO (GClosure C_PathForeachFunc) -> m (GClosure C_PathForeachFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PathForeachFunc) -> m (GClosure C_PathForeachFunc))
-> IO (GClosure C_PathForeachFunc)
-> m (GClosure C_PathForeachFunc)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: PathForeachFunc_WithClosures
cb' = PathForeachFunc -> PathForeachFunc_WithClosures
drop_closures_PathForeachFunc PathForeachFunc
cb
let cb'' :: C_PathForeachFunc
cb'' = Maybe (Ptr (FunPtr C_PathForeachFunc))
-> PathForeachFunc_WithClosures -> C_PathForeachFunc
wrap_PathForeachFunc Maybe (Ptr (FunPtr C_PathForeachFunc))
forall a. Maybe a
Nothing PathForeachFunc_WithClosures
cb'
C_PathForeachFunc -> IO (FunPtr C_PathForeachFunc)
mk_PathForeachFunc C_PathForeachFunc
cb'' IO (FunPtr C_PathForeachFunc)
-> (FunPtr C_PathForeachFunc -> IO (GClosure C_PathForeachFunc))
-> IO (GClosure C_PathForeachFunc)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PathForeachFunc -> IO (GClosure C_PathForeachFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PathForeachFunc ::
Maybe (Ptr (FunPtr C_PathForeachFunc)) ->
PathForeachFunc_WithClosures ->
C_PathForeachFunc
wrap_PathForeachFunc :: Maybe (Ptr (FunPtr C_PathForeachFunc))
-> PathForeachFunc_WithClosures -> C_PathForeachFunc
wrap_PathForeachFunc Maybe (Ptr (FunPtr C_PathForeachFunc))
gi'funptrptr PathForeachFunc_WithClosures
gi'cb CUInt
op Ptr Point
pts CSize
nPts CFloat
weight Ptr ()
userData = do
let op' :: PathOperation
op' = (Int -> PathOperation
forall a. Enum a => Int -> a
toEnum (Int -> PathOperation) -> (CUInt -> Int) -> CUInt -> PathOperation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
op
Ptr Point -> (Point -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Point
pts ((Point -> IO CInt) -> IO CInt) -> (Point -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Point
pts' -> do
let weight' :: Float
weight' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
weight
Bool
result <- PathForeachFunc_WithClosures
gi'cb PathOperation
op' Point
pts' CSize
nPts Float
weight' Ptr ()
userData
Maybe (Ptr (FunPtr C_PathForeachFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_PathForeachFunc))
gi'funptrptr
let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
result
CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
type C_ParseErrorFunc =
Ptr Gsk.ParseLocation.ParseLocation ->
Ptr Gsk.ParseLocation.ParseLocation ->
Ptr GError ->
Ptr () ->
IO ()
foreign import ccall "dynamic" __dynamic_C_ParseErrorFunc :: FunPtr C_ParseErrorFunc -> C_ParseErrorFunc
dynamic_ParseErrorFunc ::
(B.CallStack.HasCallStack, MonadIO m) =>
FunPtr C_ParseErrorFunc
-> Gsk.ParseLocation.ParseLocation
-> Gsk.ParseLocation.ParseLocation
-> GError
-> Ptr ()
-> m ()
dynamic_ParseErrorFunc :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_ParseErrorFunc
-> ParseLocation -> ParseLocation -> GError -> Ptr () -> m ()
dynamic_ParseErrorFunc FunPtr C_ParseErrorFunc
__funPtr ParseLocation
start ParseLocation
end GError
error_ Ptr ()
userData = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr ParseLocation
start' <- ParseLocation -> IO (Ptr ParseLocation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParseLocation
start
Ptr ParseLocation
end' <- ParseLocation -> IO (Ptr ParseLocation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParseLocation
end
Ptr GError
error_' <- GError -> IO (Ptr GError)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GError
error_
(FunPtr C_ParseErrorFunc -> C_ParseErrorFunc
__dynamic_C_ParseErrorFunc FunPtr C_ParseErrorFunc
__funPtr) Ptr ParseLocation
start' Ptr ParseLocation
end' Ptr GError
error_' Ptr ()
userData
ParseLocation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParseLocation
start
ParseLocation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParseLocation
end
GError -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GError
error_
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
foreign import ccall "wrapper"
mk_ParseErrorFunc :: C_ParseErrorFunc -> IO (FunPtr C_ParseErrorFunc)
type ParseErrorFunc =
Gsk.ParseLocation.ParseLocation
-> Gsk.ParseLocation.ParseLocation
-> GError
-> IO ()
noParseErrorFunc :: Maybe ParseErrorFunc
noParseErrorFunc :: Maybe ParseErrorFunc
noParseErrorFunc = Maybe ParseErrorFunc
forall a. Maybe a
Nothing
type ParseErrorFunc_WithClosures =
Gsk.ParseLocation.ParseLocation
-> Gsk.ParseLocation.ParseLocation
-> GError
-> Ptr ()
-> IO ()
noParseErrorFunc_WithClosures :: Maybe ParseErrorFunc_WithClosures
noParseErrorFunc_WithClosures :: Maybe ParseErrorFunc_WithClosures
noParseErrorFunc_WithClosures = Maybe ParseErrorFunc_WithClosures
forall a. Maybe a
Nothing
drop_closures_ParseErrorFunc :: ParseErrorFunc -> ParseErrorFunc_WithClosures
drop_closures_ParseErrorFunc :: ParseErrorFunc -> ParseErrorFunc_WithClosures
drop_closures_ParseErrorFunc ParseErrorFunc
_f ParseLocation
start ParseLocation
end GError
error_ Ptr ()
_ = ParseErrorFunc
_f ParseLocation
start ParseLocation
end GError
error_
genClosure_ParseErrorFunc :: MonadIO m => ParseErrorFunc -> m (GClosure C_ParseErrorFunc)
genClosure_ParseErrorFunc :: forall (m :: * -> *).
MonadIO m =>
ParseErrorFunc -> m (GClosure C_ParseErrorFunc)
genClosure_ParseErrorFunc ParseErrorFunc
cb = IO (GClosure C_ParseErrorFunc) -> m (GClosure C_ParseErrorFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ParseErrorFunc) -> m (GClosure C_ParseErrorFunc))
-> IO (GClosure C_ParseErrorFunc) -> m (GClosure C_ParseErrorFunc)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: ParseErrorFunc_WithClosures
cb' = ParseErrorFunc -> ParseErrorFunc_WithClosures
drop_closures_ParseErrorFunc ParseErrorFunc
cb
let cb'' :: C_ParseErrorFunc
cb'' = Maybe (Ptr (FunPtr C_ParseErrorFunc))
-> ParseErrorFunc_WithClosures -> C_ParseErrorFunc
wrap_ParseErrorFunc Maybe (Ptr (FunPtr C_ParseErrorFunc))
forall a. Maybe a
Nothing ParseErrorFunc_WithClosures
cb'
C_ParseErrorFunc -> IO (FunPtr C_ParseErrorFunc)
mk_ParseErrorFunc C_ParseErrorFunc
cb'' IO (FunPtr C_ParseErrorFunc)
-> (FunPtr C_ParseErrorFunc -> IO (GClosure C_ParseErrorFunc))
-> IO (GClosure C_ParseErrorFunc)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ParseErrorFunc -> IO (GClosure C_ParseErrorFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ParseErrorFunc ::
Maybe (Ptr (FunPtr C_ParseErrorFunc)) ->
ParseErrorFunc_WithClosures ->
C_ParseErrorFunc
wrap_ParseErrorFunc :: Maybe (Ptr (FunPtr C_ParseErrorFunc))
-> ParseErrorFunc_WithClosures -> C_ParseErrorFunc
wrap_ParseErrorFunc Maybe (Ptr (FunPtr C_ParseErrorFunc))
gi'funptrptr ParseErrorFunc_WithClosures
gi'cb Ptr ParseLocation
start Ptr ParseLocation
end Ptr GError
error_ Ptr ()
userData = do
ParseLocation
start' <- ((ManagedPtr ParseLocation -> ParseLocation)
-> Ptr ParseLocation -> IO ParseLocation
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr ParseLocation -> ParseLocation
Gsk.ParseLocation.ParseLocation) Ptr ParseLocation
start
ParseLocation
end' <- ((ManagedPtr ParseLocation -> ParseLocation)
-> Ptr ParseLocation -> IO ParseLocation
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr ParseLocation -> ParseLocation
Gsk.ParseLocation.ParseLocation) Ptr ParseLocation
end
GError
error_' <- ((ManagedPtr GError -> GError) -> Ptr GError -> IO GError
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GError -> GError
GError) Ptr GError
error_
ParseErrorFunc_WithClosures
gi'cb ParseLocation
start' ParseLocation
end' GError
error_' Ptr ()
userData
Maybe (Ptr (FunPtr C_ParseErrorFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_ParseErrorFunc))
gi'funptrptr