{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gsk.Structs.Path
(
Path(..) ,
#if defined(ENABLE_OVERLOADING)
ResolvePathMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PathForeachMethodInfo ,
#endif
pathForeach ,
#if defined(ENABLE_OVERLOADING)
PathGetBoundsMethodInfo ,
#endif
pathGetBounds ,
#if defined(ENABLE_OVERLOADING)
PathGetStrokeBoundsMethodInfo ,
#endif
pathGetStrokeBounds ,
#if defined(ENABLE_OVERLOADING)
PathInFillMethodInfo ,
#endif
pathInFill ,
#if defined(ENABLE_OVERLOADING)
PathIsClosedMethodInfo ,
#endif
pathIsClosed ,
#if defined(ENABLE_OVERLOADING)
PathIsEmptyMethodInfo ,
#endif
pathIsEmpty ,
pathParse ,
#if defined(ENABLE_OVERLOADING)
PathPrintMethodInfo ,
#endif
pathPrint ,
#if defined(ENABLE_OVERLOADING)
PathRefMethodInfo ,
#endif
pathRef ,
#if defined(ENABLE_OVERLOADING)
PathToCairoMethodInfo ,
#endif
pathToCairo ,
#if defined(ENABLE_OVERLOADING)
PathToStringMethodInfo ,
#endif
pathToString ,
#if defined(ENABLE_OVERLOADING)
PathUnrefMethodInfo ,
#endif
pathUnref ,
) 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.Cairo.Structs.Context as Cairo.Context
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Gsk.Callbacks as Gsk.Callbacks
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
import {-# SOURCE #-} qualified GI.Gsk.Flags as Gsk.Flags
import {-# SOURCE #-} qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
#else
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Gsk.Callbacks as Gsk.Callbacks
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
import {-# SOURCE #-} qualified GI.Gsk.Flags as Gsk.Flags
import {-# SOURCE #-} qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
#endif
newtype Path = Path (SP.ManagedPtr Path)
deriving (Path -> Path -> Bool
(Path -> Path -> Bool) -> (Path -> Path -> Bool) -> Eq Path
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Path -> Path -> Bool
== :: Path -> Path -> Bool
$c/= :: Path -> Path -> Bool
/= :: Path -> Path -> Bool
Eq)
instance SP.ManagedPtrNewtype Path where
toManagedPtr :: Path -> ManagedPtr Path
toManagedPtr (Path ManagedPtr Path
p) = ManagedPtr Path
p
foreign import ccall "gsk_path_get_type" c_gsk_path_get_type ::
IO GType
type instance O.ParentTypes Path = '[]
instance O.HasParentTypes Path
instance B.Types.TypedObject Path where
glibType :: IO GType
glibType = IO GType
c_gsk_path_get_type
instance B.Types.GBoxed Path
instance B.GValue.IsGValue (Maybe Path) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gsk_path_get_type
gvalueSet_ :: Ptr GValue -> Maybe Path -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Path
P.Nothing = Ptr GValue -> Ptr Path -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Path
forall a. Ptr a
FP.nullPtr :: FP.Ptr Path)
gvalueSet_ Ptr GValue
gv (P.Just Path
obj) = Path -> (Ptr Path -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Path
obj (Ptr GValue -> Ptr Path -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Path)
gvalueGet_ Ptr GValue
gv = do
Ptr Path
ptr <- Ptr GValue -> IO (Ptr Path)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Path)
if Ptr Path
ptr Ptr Path -> Ptr Path -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Path
forall a. Ptr a
FP.nullPtr
then Path -> Maybe Path
forall a. a -> Maybe a
P.Just (Path -> Maybe Path) -> IO Path -> IO (Maybe Path)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Path -> Path) -> Ptr Path -> IO Path
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Path -> Path
Path Ptr Path
ptr
else Maybe Path -> IO (Maybe Path)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Path
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Path
type instance O.AttributeList Path = PathAttributeList
type PathAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gsk_path_foreach" gsk_path_foreach ::
Ptr Path ->
CUInt ->
FunPtr Gsk.Callbacks.C_PathForeachFunc ->
Ptr () ->
IO CInt
pathForeach ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> [Gsk.Flags.PathForeachFlags]
-> Gsk.Callbacks.PathForeachFunc
-> m Bool
pathForeach :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Path -> [PathForeachFlags] -> PathForeachFunc -> m Bool
pathForeach Path
self [PathForeachFlags]
flags PathForeachFunc
func = 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
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
let flags' :: CUInt
flags' = [PathForeachFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [PathForeachFlags]
flags
FunPtr C_PathForeachFunc
func' <- C_PathForeachFunc -> IO (FunPtr C_PathForeachFunc)
Gsk.Callbacks.mk_PathForeachFunc (Maybe (Ptr (FunPtr C_PathForeachFunc))
-> PathForeachFunc_WithClosures -> C_PathForeachFunc
Gsk.Callbacks.wrap_PathForeachFunc Maybe (Ptr (FunPtr C_PathForeachFunc))
forall a. Maybe a
Nothing (PathForeachFunc -> PathForeachFunc_WithClosures
Gsk.Callbacks.drop_closures_PathForeachFunc PathForeachFunc
func))
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
CInt
result <- Ptr Path -> CUInt -> FunPtr C_PathForeachFunc -> Ptr () -> IO CInt
gsk_path_foreach Ptr Path
self' CUInt
flags' FunPtr C_PathForeachFunc
func' Ptr ()
forall a. Ptr a
userData
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_PathForeachFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_PathForeachFunc
func'
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PathForeachMethodInfo
instance (signature ~ ([Gsk.Flags.PathForeachFlags] -> Gsk.Callbacks.PathForeachFunc -> m Bool), MonadIO m) => O.OverloadedMethod PathForeachMethodInfo Path signature where
overloadedMethod = pathForeach
instance O.OverloadedMethodInfo PathForeachMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathForeach",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathForeach"
})
#endif
foreign import ccall "gsk_path_get_bounds" gsk_path_get_bounds ::
Ptr Path ->
Ptr Graphene.Rect.Rect ->
IO CInt
pathGetBounds ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> m ((Bool, Graphene.Rect.Rect))
pathGetBounds :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Path -> m (Bool, Rect)
pathGetBounds Path
self = IO (Bool, Rect) -> m (Bool, Rect)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Rect) -> m (Bool, Rect))
-> IO (Bool, Rect) -> m (Bool, Rect)
forall a b. (a -> b) -> a -> b
$ do
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
Ptr Rect
bounds <- Int -> IO (Ptr Rect)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Rect.Rect)
CInt
result <- Ptr Path -> Ptr Rect -> IO CInt
gsk_path_get_bounds Ptr Path
self' Ptr Rect
bounds
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Rect
bounds' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Graphene.Rect.Rect) Ptr Rect
bounds
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
(Bool, Rect) -> IO (Bool, Rect)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Rect
bounds')
#if defined(ENABLE_OVERLOADING)
data PathGetBoundsMethodInfo
instance (signature ~ (m ((Bool, Graphene.Rect.Rect))), MonadIO m) => O.OverloadedMethod PathGetBoundsMethodInfo Path signature where
overloadedMethod = pathGetBounds
instance O.OverloadedMethodInfo PathGetBoundsMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathGetBounds",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathGetBounds"
})
#endif
foreign import ccall "gsk_path_get_stroke_bounds" gsk_path_get_stroke_bounds ::
Ptr Path ->
Ptr Gsk.Stroke.Stroke ->
Ptr Graphene.Rect.Rect ->
IO CInt
pathGetStrokeBounds ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> Gsk.Stroke.Stroke
-> m ((Bool, Graphene.Rect.Rect))
pathGetStrokeBounds :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Path -> Stroke -> m (Bool, Rect)
pathGetStrokeBounds Path
self Stroke
stroke = IO (Bool, Rect) -> m (Bool, Rect)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Rect) -> m (Bool, Rect))
-> IO (Bool, Rect) -> m (Bool, Rect)
forall a b. (a -> b) -> a -> b
$ do
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
Ptr Stroke
stroke' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
stroke
Ptr Rect
bounds <- Int -> IO (Ptr Rect)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Rect.Rect)
CInt
result <- Ptr Path -> Ptr Stroke -> Ptr Rect -> IO CInt
gsk_path_get_stroke_bounds Ptr Path
self' Ptr Stroke
stroke' Ptr Rect
bounds
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Rect
bounds' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Graphene.Rect.Rect) Ptr Rect
bounds
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
stroke
(Bool, Rect) -> IO (Bool, Rect)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Rect
bounds')
#if defined(ENABLE_OVERLOADING)
data PathGetStrokeBoundsMethodInfo
instance (signature ~ (Gsk.Stroke.Stroke -> m ((Bool, Graphene.Rect.Rect))), MonadIO m) => O.OverloadedMethod PathGetStrokeBoundsMethodInfo Path signature where
overloadedMethod = pathGetStrokeBounds
instance O.OverloadedMethodInfo PathGetStrokeBoundsMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathGetStrokeBounds",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathGetStrokeBounds"
})
#endif
foreign import ccall "gsk_path_in_fill" gsk_path_in_fill ::
Ptr Path ->
Ptr Graphene.Point.Point ->
CUInt ->
IO CInt
pathInFill ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> Graphene.Point.Point
-> Gsk.Enums.FillRule
-> m Bool
pathInFill :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Path -> Point -> FillRule -> m Bool
pathInFill Path
self Point
point FillRule
fillRule = 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
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
Ptr Point
point' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
point
let fillRule' :: CUInt
fillRule' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (FillRule -> Int) -> FillRule -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FillRule -> Int
forall a. Enum a => a -> Int
fromEnum) FillRule
fillRule
CInt
result <- Ptr Path -> Ptr Point -> CUInt -> IO CInt
gsk_path_in_fill Ptr Path
self' Ptr Point
point' CUInt
fillRule'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
point
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PathInFillMethodInfo
instance (signature ~ (Graphene.Point.Point -> Gsk.Enums.FillRule -> m Bool), MonadIO m) => O.OverloadedMethod PathInFillMethodInfo Path signature where
overloadedMethod = pathInFill
instance O.OverloadedMethodInfo PathInFillMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathInFill",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathInFill"
})
#endif
foreign import ccall "gsk_path_is_closed" gsk_path_is_closed ::
Ptr Path ->
IO CInt
pathIsClosed ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> m Bool
pathIsClosed :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Path -> m Bool
pathIsClosed Path
self = 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
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
CInt
result <- Ptr Path -> IO CInt
gsk_path_is_closed Ptr Path
self'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PathIsClosedMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod PathIsClosedMethodInfo Path signature where
overloadedMethod = pathIsClosed
instance O.OverloadedMethodInfo PathIsClosedMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathIsClosed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathIsClosed"
})
#endif
foreign import ccall "gsk_path_is_empty" gsk_path_is_empty ::
Ptr Path ->
IO CInt
pathIsEmpty ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> m Bool
pathIsEmpty :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Path -> m Bool
pathIsEmpty Path
self = 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
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
CInt
result <- Ptr Path -> IO CInt
gsk_path_is_empty Ptr Path
self'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PathIsEmptyMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod PathIsEmptyMethodInfo Path signature where
overloadedMethod = pathIsEmpty
instance O.OverloadedMethodInfo PathIsEmptyMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathIsEmpty",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathIsEmpty"
})
#endif
foreign import ccall "gsk_path_print" gsk_path_print ::
Ptr Path ->
Ptr GLib.String.String ->
IO ()
pathPrint ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> GLib.String.String
-> m ()
pathPrint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Path -> String -> m ()
pathPrint Path
self String
string = 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 Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
Ptr Path -> Ptr String -> IO ()
gsk_path_print Ptr Path
self' Ptr String
string'
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PathPrintMethodInfo
instance (signature ~ (GLib.String.String -> m ()), MonadIO m) => O.OverloadedMethod PathPrintMethodInfo Path signature where
overloadedMethod = pathPrint
instance O.OverloadedMethodInfo PathPrintMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathPrint",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathPrint"
})
#endif
foreign import ccall "gsk_path_ref" gsk_path_ref ::
Ptr Path ->
IO (Ptr Path)
pathRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> m Path
pathRef :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Path -> m Path
pathRef Path
self = IO Path -> m Path
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Path -> m Path) -> IO Path -> m Path
forall a b. (a -> b) -> a -> b
$ do
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
Ptr Path
result <- Ptr Path -> IO (Ptr Path)
gsk_path_ref Ptr Path
self'
Text -> Ptr Path -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pathRef" Ptr Path
result
Path
result' <- ((ManagedPtr Path -> Path) -> Ptr Path -> IO Path
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Path -> Path
Path) Ptr Path
result
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Path -> IO Path
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Path
result'
#if defined(ENABLE_OVERLOADING)
data PathRefMethodInfo
instance (signature ~ (m Path), MonadIO m) => O.OverloadedMethod PathRefMethodInfo Path signature where
overloadedMethod = pathRef
instance O.OverloadedMethodInfo PathRefMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathRef"
})
#endif
foreign import ccall "gsk_path_to_cairo" gsk_path_to_cairo ::
Ptr Path ->
Ptr Cairo.Context.Context ->
IO ()
pathToCairo ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> Cairo.Context.Context
-> m ()
pathToCairo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Path -> Context -> m ()
pathToCairo Path
self Context
cr = 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 Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
Ptr Context
cr' <- Context -> IO (Ptr Context)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Context
cr
Ptr Path -> Ptr Context -> IO ()
gsk_path_to_cairo Ptr Path
self' Ptr Context
cr'
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Context -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Context
cr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PathToCairoMethodInfo
instance (signature ~ (Cairo.Context.Context -> m ()), MonadIO m) => O.OverloadedMethod PathToCairoMethodInfo Path signature where
overloadedMethod = pathToCairo
instance O.OverloadedMethodInfo PathToCairoMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathToCairo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathToCairo"
})
#endif
foreign import ccall "gsk_path_to_string" gsk_path_to_string ::
Ptr Path ->
IO CString
pathToString ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> m T.Text
pathToString :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Path -> m Text
pathToString Path
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
CString
result <- Ptr Path -> IO CString
gsk_path_to_string Ptr Path
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pathToString" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data PathToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod PathToStringMethodInfo Path signature where
overloadedMethod = pathToString
instance O.OverloadedMethodInfo PathToStringMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathToString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathToString"
})
#endif
foreign import ccall "gsk_path_unref" gsk_path_unref ::
Ptr Path ->
IO ()
pathUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
Path
-> m ()
pathUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Path -> m ()
pathUnref Path
self = 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 Path
self' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
self
Ptr Path -> IO ()
gsk_path_unref Ptr Path
self'
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PathUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod PathUnrefMethodInfo Path signature where
overloadedMethod = pathUnref
instance O.OverloadedMethodInfo PathUnrefMethodInfo Path where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Path.pathUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Path.html#v:pathUnref"
})
#endif
foreign import ccall "gsk_path_parse" gsk_path_parse ::
CString ->
IO (Ptr Path)
pathParse ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m (Maybe Path)
pathParse :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe Path)
pathParse Text
string = IO (Maybe Path) -> m (Maybe Path)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Path) -> m (Maybe Path))
-> IO (Maybe Path) -> m (Maybe Path)
forall a b. (a -> b) -> a -> b
$ do
CString
string' <- Text -> IO CString
textToCString Text
string
Ptr Path
result <- CString -> IO (Ptr Path)
gsk_path_parse CString
string'
Maybe Path
maybeResult <- Ptr Path -> (Ptr Path -> IO Path) -> IO (Maybe Path)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Path
result ((Ptr Path -> IO Path) -> IO (Maybe Path))
-> (Ptr Path -> IO Path) -> IO (Maybe Path)
forall a b. (a -> b) -> a -> b
$ \Ptr Path
result' -> do
Path
result'' <- ((ManagedPtr Path -> Path) -> Ptr Path -> IO Path
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Path -> Path
Path) Ptr Path
result'
Path -> IO Path
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Path
result''
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
Maybe Path -> IO (Maybe Path)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Path
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePathMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePathMethod "foreach" o = PathForeachMethodInfo
ResolvePathMethod "inFill" o = PathInFillMethodInfo
ResolvePathMethod "isClosed" o = PathIsClosedMethodInfo
ResolvePathMethod "isEmpty" o = PathIsEmptyMethodInfo
ResolvePathMethod "print" o = PathPrintMethodInfo
ResolvePathMethod "ref" o = PathRefMethodInfo
ResolvePathMethod "toCairo" o = PathToCairoMethodInfo
ResolvePathMethod "toString" o = PathToStringMethodInfo
ResolvePathMethod "unref" o = PathUnrefMethodInfo
ResolvePathMethod "getBounds" o = PathGetBoundsMethodInfo
ResolvePathMethod "getStrokeBounds" o = PathGetStrokeBoundsMethodInfo
ResolvePathMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePathMethod t Path, O.OverloadedMethod info Path p) => OL.IsLabel t (Path -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePathMethod t Path, O.OverloadedMethod info Path p, R.HasField t Path p) => R.HasField t Path p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePathMethod t Path, O.OverloadedMethodInfo info Path) => OL.IsLabel t (O.MethodProxy info Path) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif