{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A point with two coordinates.
-- 
-- /Since: 1.0/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Graphene.Structs.Point
    ( 

-- * Exported types
    Point(..)                               ,
    newZeroPoint                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [distance]("GI.Graphene.Structs.Point#g:method:distance"), [equal]("GI.Graphene.Structs.Point#g:method:equal"), [free]("GI.Graphene.Structs.Point#g:method:free"), [init]("GI.Graphene.Structs.Point#g:method:init"), [initFromPoint]("GI.Graphene.Structs.Point#g:method:initFromPoint"), [initFromVec2]("GI.Graphene.Structs.Point#g:method:initFromVec2"), [interpolate]("GI.Graphene.Structs.Point#g:method:interpolate"), [near]("GI.Graphene.Structs.Point#g:method:near"), [toVec2]("GI.Graphene.Structs.Point#g:method:toVec2").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolvePointMethod                      ,
#endif

-- ** alloc #method:alloc#

    pointAlloc                              ,


-- ** distance #method:distance#

#if defined(ENABLE_OVERLOADING)
    PointDistanceMethodInfo                 ,
#endif
    pointDistance                           ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    PointEqualMethodInfo                    ,
#endif
    pointEqual                              ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    PointFreeMethodInfo                     ,
#endif
    pointFree                               ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    PointInitMethodInfo                     ,
#endif
    pointInit                               ,


-- ** initFromPoint #method:initFromPoint#

#if defined(ENABLE_OVERLOADING)
    PointInitFromPointMethodInfo            ,
#endif
    pointInitFromPoint                      ,


-- ** initFromVec2 #method:initFromVec2#

#if defined(ENABLE_OVERLOADING)
    PointInitFromVec2MethodInfo             ,
#endif
    pointInitFromVec2                       ,


-- ** interpolate #method:interpolate#

#if defined(ENABLE_OVERLOADING)
    PointInterpolateMethodInfo              ,
#endif
    pointInterpolate                        ,


-- ** near #method:near#

#if defined(ENABLE_OVERLOADING)
    PointNearMethodInfo                     ,
#endif
    pointNear                               ,


-- ** toVec2 #method:toVec2#

#if defined(ENABLE_OVERLOADING)
    PointToVec2MethodInfo                   ,
#endif
    pointToVec2                             ,


-- ** zero #method:zero#

    pointZero                               ,




 -- * Properties


-- ** x #attr:x#
-- | the X coordinate of the point

    getPointX                               ,
#if defined(ENABLE_OVERLOADING)
    point_x                                 ,
#endif
    setPointX                               ,


-- ** y #attr:y#
-- | the Y coordinate of the point

    getPointY                               ,
#if defined(ENABLE_OVERLOADING)
    point_y                                 ,
#endif
    setPointY                               ,




    ) 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.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 {-# SOURCE #-} qualified GI.Graphene.Structs.Vec2 as Graphene.Vec2

-- | Memory-managed wrapper type.
newtype Point = Point (SP.ManagedPtr Point)
    deriving (Point -> Point -> Bool
(Point -> Point -> Bool) -> (Point -> Point -> Bool) -> Eq Point
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Point -> Point -> Bool
== :: Point -> Point -> Bool
$c/= :: Point -> Point -> Bool
/= :: Point -> Point -> Bool
Eq)

instance SP.ManagedPtrNewtype Point where
    toManagedPtr :: Point -> ManagedPtr Point
toManagedPtr (Point ManagedPtr Point
p) = ManagedPtr Point
p

foreign import ccall "graphene_point_get_type" c_graphene_point_get_type :: 
    IO GType

type instance O.ParentTypes Point = '[]
instance O.HasParentTypes Point

instance B.Types.TypedObject Point where
    glibType :: IO GType
glibType = IO GType
c_graphene_point_get_type

instance B.Types.GBoxed Point

-- | Convert 'Point' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Point) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_graphene_point_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Point -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Point
P.Nothing = Ptr GValue -> Ptr Point -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Point
forall a. Ptr a
FP.nullPtr :: FP.Ptr Point)
    gvalueSet_ Ptr GValue
gv (P.Just Point
obj) = Point -> (Ptr Point -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Point
obj (Ptr GValue -> Ptr Point -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Point)
gvalueGet_ Ptr GValue
gv = do
        Ptr Point
ptr <- Ptr GValue -> IO (Ptr Point)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Point)
        if Ptr Point
ptr Ptr Point -> Ptr Point -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Point
forall a. Ptr a
FP.nullPtr
        then Point -> Maybe Point
forall a. a -> Maybe a
P.Just (Point -> Maybe Point) -> IO Point -> IO (Maybe Point)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Point -> Point
Point Ptr Point
ptr
        else Maybe Point -> IO (Maybe Point)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Point
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `Point` struct initialized to zero.
newZeroPoint :: MonadIO m => m Point
newZeroPoint :: forall (m :: * -> *). MonadIO m => m Point
newZeroPoint = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Point)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
8 IO (Ptr Point) -> (Ptr Point -> IO Point) -> IO Point
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Point

instance tag ~ 'AttrSet => Constructible Point tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr Point -> Point) -> [AttrOp Point tag] -> m Point
new ManagedPtr Point -> Point
_ [AttrOp Point tag]
attrs = do
        Point
o <- m Point
forall (m :: * -> *). MonadIO m => m Point
newZeroPoint
        Point -> [AttrOp Point 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Point
o [AttrOp Point tag]
[AttrOp Point 'AttrSet]
attrs
        Point -> m Point
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
o


-- | Get the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' point #x
-- @
getPointX :: MonadIO m => Point -> m Float
getPointX :: forall (m :: * -> *). MonadIO m => Point -> m Float
getPointX Point
s = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ Point -> (Ptr Point -> IO Float) -> IO Float
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Point
s ((Ptr Point -> IO Float) -> IO Float)
-> (Ptr Point -> IO Float) -> IO Float
forall a b. (a -> b) -> a -> b
$ \Ptr Point
ptr -> do
    CFloat
val <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek (Ptr Point
ptr Ptr Point -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CFloat
    let val' :: Float
val' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
val
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
val'

-- | Set the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' point [ #x 'Data.GI.Base.Attributes.:=' value ]
-- @
setPointX :: MonadIO m => Point -> Float -> m ()
setPointX :: forall (m :: * -> *). MonadIO m => Point -> Float -> m ()
setPointX Point
s Float
val = 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
$ Point -> (Ptr Point -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Point
s ((Ptr Point -> IO ()) -> IO ()) -> (Ptr Point -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Point
ptr -> do
    let val' :: CFloat
val' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
val
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Point
ptr Ptr Point -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CFloat
val' :: CFloat)

#if defined(ENABLE_OVERLOADING)
data PointXFieldInfo
instance AttrInfo PointXFieldInfo where
    type AttrBaseTypeConstraint PointXFieldInfo = (~) Point
    type AttrAllowedOps PointXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint PointXFieldInfo = (~) Float
    type AttrTransferTypeConstraint PointXFieldInfo = (~)Float
    type AttrTransferType PointXFieldInfo = Float
    type AttrGetType PointXFieldInfo = Float
    type AttrLabel PointXFieldInfo = "x"
    type AttrOrigin PointXFieldInfo = Point
    attrGet = getPointX
    attrSet = setPointX
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.x"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#g:attr:x"
        })

point_x :: AttrLabelProxy "x"
point_x = AttrLabelProxy

#endif


-- | Get the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' point #y
-- @
getPointY :: MonadIO m => Point -> m Float
getPointY :: forall (m :: * -> *). MonadIO m => Point -> m Float
getPointY Point
s = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ Point -> (Ptr Point -> IO Float) -> IO Float
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Point
s ((Ptr Point -> IO Float) -> IO Float)
-> (Ptr Point -> IO Float) -> IO Float
forall a b. (a -> b) -> a -> b
$ \Ptr Point
ptr -> do
    CFloat
val <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek (Ptr Point
ptr Ptr Point -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO CFloat
    let val' :: Float
val' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
val
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
val'

-- | Set the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' point [ #y 'Data.GI.Base.Attributes.:=' value ]
-- @
setPointY :: MonadIO m => Point -> Float -> m ()
setPointY :: forall (m :: * -> *). MonadIO m => Point -> Float -> m ()
setPointY Point
s Float
val = 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
$ Point -> (Ptr Point -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Point
s ((Ptr Point -> IO ()) -> IO ()) -> (Ptr Point -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Point
ptr -> do
    let val' :: CFloat
val' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
val
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Point
ptr Ptr Point -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (CFloat
val' :: CFloat)

#if defined(ENABLE_OVERLOADING)
data PointYFieldInfo
instance AttrInfo PointYFieldInfo where
    type AttrBaseTypeConstraint PointYFieldInfo = (~) Point
    type AttrAllowedOps PointYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint PointYFieldInfo = (~) Float
    type AttrTransferTypeConstraint PointYFieldInfo = (~)Float
    type AttrTransferType PointYFieldInfo = Float
    type AttrGetType PointYFieldInfo = Float
    type AttrLabel PointYFieldInfo = "y"
    type AttrOrigin PointYFieldInfo = Point
    attrGet = getPointY
    attrSet = setPointY
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.y"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#g:attr:y"
        })

point_y :: AttrLabelProxy "y"
point_y = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Point
type instance O.AttributeList Point = PointAttributeList
type PointAttributeList = ('[ '("x", PointXFieldInfo), '("y", PointYFieldInfo)] :: [(Symbol, *)])
#endif

-- method Point::alloc
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Point" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_alloc" graphene_point_alloc :: 
    IO (Ptr Point)

-- | Allocates a new t'GI.Graphene.Structs.Point.Point' structure.
-- 
-- The coordinates of the returned point are (0, 0).
-- 
-- It\'s possible to chain this function with 'GI.Graphene.Structs.Point.pointInit'
-- or 'GI.Graphene.Structs.Point.pointInitFromPoint', e.g.:
-- 
-- 
-- === /C code/
-- >
-- >  graphene_point_t *
-- >  point_new (float x, float y)
-- >  {
-- >    return graphene_point_init (graphene_point_alloc (), x, y);
-- >  }
-- >
-- >  graphene_point_t *
-- >  point_copy (const graphene_point_t *p)
-- >  {
-- >    return graphene_point_init_from_point (graphene_point_alloc (), p);
-- >  }
-- 
-- 
-- /Since: 1.0/
pointAlloc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Point
    -- ^ __Returns:__ the newly allocated t'GI.Graphene.Structs.Point.Point'.
    --   Use 'GI.Graphene.Structs.Point.pointFree' to free the resources allocated by
    --   this function.
pointAlloc :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Point
pointAlloc  = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
result <- IO (Ptr Point)
graphene_point_alloc
    Text -> Ptr Point -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pointAlloc" Ptr Point
result
    Point
result' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Point) Ptr Point
result
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Point::distance
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance component on the X axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "d_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance component on the Y axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_distance" graphene_point_distance :: 
    Ptr Point ->                            -- a : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Point ->                            -- b : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr CFloat ->                           -- d_x : TBasicType TFloat
    Ptr CFloat ->                           -- d_y : TBasicType TFloat
    IO CFloat

-- | Computes the distance between /@a@/ and /@b@/.
-- 
-- /Since: 1.0/
pointDistance ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@a@/: a t'GI.Graphene.Structs.Point.Point'
    -> Point
    -- ^ /@b@/: a t'GI.Graphene.Structs.Point.Point'
    -> m ((Float, Float, Float))
    -- ^ __Returns:__ the distance between the two points
pointDistance :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Point -> Point -> m (Float, Float, Float)
pointDistance Point
a Point
b = IO (Float, Float, Float) -> m (Float, Float, Float)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float, Float) -> m (Float, Float, Float))
-> IO (Float, Float, Float) -> m (Float, Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
a' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
a
    Ptr Point
b' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
b
    Ptr CFloat
dX <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
dY <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    CFloat
result <- Ptr Point -> Ptr Point -> Ptr CFloat -> Ptr CFloat -> IO CFloat
graphene_point_distance Ptr Point
a' Ptr Point
b' Ptr CFloat
dX Ptr CFloat
dY
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    CFloat
dX' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
dX
    let dX'' :: Float
dX'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
dX'
    CFloat
dY' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
dY
    let dY'' :: Float
dY'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
dY'
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
a
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
b
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
dX
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
dY
    (Float, Float, Float) -> IO (Float, Float, Float)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
result', Float
dX'', Float
dY'')

#if defined(ENABLE_OVERLOADING)
data PointDistanceMethodInfo
instance (signature ~ (Point -> m ((Float, Float, Float))), MonadIO m) => O.OverloadedMethod PointDistanceMethodInfo Point signature where
    overloadedMethod = pointDistance

instance O.OverloadedMethodInfo PointDistanceMethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointDistance",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointDistance"
        })


#endif

-- method Point::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_equal" graphene_point_equal :: 
    Ptr Point ->                            -- a : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Point ->                            -- b : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO CInt

-- | Checks if the two points /@a@/ and /@b@/ point to the same
-- coordinates.
-- 
-- This function accounts for floating point fluctuations; if
-- you want to control the fuzziness of the match, you can use
-- 'GI.Graphene.Structs.Point.pointNear' instead.
-- 
-- /Since: 1.0/
pointEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@a@/: a t'GI.Graphene.Structs.Point.Point'
    -> Point
    -- ^ /@b@/: a t'GI.Graphene.Structs.Point.Point'
    -> m Bool
    -- ^ __Returns:__ @true@ if the points have the same coordinates
pointEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Point -> Point -> m Bool
pointEqual Point
a Point
b = 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 Point
a' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
a
    Ptr Point
b' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
b
    CInt
result <- Ptr Point -> Ptr Point -> IO CInt
graphene_point_equal Ptr Point
a' Ptr Point
b'
    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
a
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
b
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PointEqualMethodInfo
instance (signature ~ (Point -> m Bool), MonadIO m) => O.OverloadedMethod PointEqualMethodInfo Point signature where
    overloadedMethod = pointEqual

instance O.OverloadedMethodInfo PointEqualMethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointEqual",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointEqual"
        })


#endif

-- method Point::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_free" graphene_point_free :: 
    Ptr Point ->                            -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Frees the resources allocated by 'GI.Graphene.Structs.Point.pointAlloc'.
-- 
-- /Since: 1.0/
pointFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> m ()
pointFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Point -> m ()
pointFree Point
p = 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 Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Point -> IO ()
graphene_point_free Ptr Point
p'
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PointFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod PointFreeMethodInfo Point signature where
    overloadedMethod = pointFree

instance O.OverloadedMethodInfo PointFreeMethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointFree"
        })


#endif

-- method Point::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the X coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the Y coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Point" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_init" graphene_point_init :: 
    Ptr Point ->                            -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    CFloat ->                               -- x : TBasicType TFloat
    CFloat ->                               -- y : TBasicType TFloat
    IO (Ptr Point)

-- | Initializes /@p@/ to the given /@x@/ and /@y@/ coordinates.
-- 
-- It\'s safe to call this function multiple times.
-- 
-- /Since: 1.0/
pointInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> Float
    -- ^ /@x@/: the X coordinate
    -> Float
    -- ^ /@y@/: the Y coordinate
    -> m Point
    -- ^ __Returns:__ the initialized point
pointInit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Point -> Float -> Float -> m Point
pointInit Point
p Float
x Float
y = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    let x' :: CFloat
x' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x
    let y' :: CFloat
y' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y
    Ptr Point
result <- Ptr Point -> CFloat -> CFloat -> IO (Ptr Point)
graphene_point_init Ptr Point
p' CFloat
x' CFloat
y'
    Text -> Ptr Point -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pointInit" Ptr Point
result
    Point
result' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Point -> Point
Point) Ptr Point
result
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
result'

#if defined(ENABLE_OVERLOADING)
data PointInitMethodInfo
instance (signature ~ (Float -> Float -> m Point), MonadIO m) => O.OverloadedMethod PointInitMethodInfo Point signature where
    overloadedMethod = pointInit

instance O.OverloadedMethodInfo PointInitMethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointInit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointInit"
        })


#endif

-- method Point::init_from_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_point_t to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Point" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_init_from_point" graphene_point_init_from_point :: 
    Ptr Point ->                            -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Point ->                            -- src : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO (Ptr Point)

-- | Initializes /@p@/ with the same coordinates of /@src@/.
-- 
-- /Since: 1.0/
pointInitFromPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> Point
    -- ^ /@src@/: the t'GI.Graphene.Structs.Point.Point' to use
    -> m Point
    -- ^ __Returns:__ the initialized point
pointInitFromPoint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Point -> Point -> m Point
pointInitFromPoint Point
p Point
src = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Point
src' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
src
    Ptr Point
result <- Ptr Point -> Ptr Point -> IO (Ptr Point)
graphene_point_init_from_point Ptr Point
p' Ptr Point
src'
    Text -> Ptr Point -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pointInitFromPoint" Ptr Point
result
    Point
result' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Point -> Point
Point) Ptr Point
result
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
src
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
result'

#if defined(ENABLE_OVERLOADING)
data PointInitFromPointMethodInfo
instance (signature ~ (Point -> m Point), MonadIO m) => O.OverloadedMethod PointInitFromPointMethodInfo Point signature where
    overloadedMethod = pointInitFromPoint

instance O.OverloadedMethodInfo PointInitFromPointMethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointInitFromPoint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointInitFromPoint"
        })


#endif

-- method Point::init_from_vec2
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #graphene_point_t to initialize"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_vec2_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Point" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_init_from_vec2" graphene_point_init_from_vec2 :: 
    Ptr Point ->                            -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Graphene.Vec2.Vec2 ->               -- src : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO (Ptr Point)

-- | Initializes /@p@/ with the coordinates inside the given t'GI.Graphene.Structs.Vec2.Vec2'.
-- 
-- /Since: 1.4/
pointInitFromVec2 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@p@/: the t'GI.Graphene.Structs.Point.Point' to initialize
    -> Graphene.Vec2.Vec2
    -- ^ /@src@/: a t'GI.Graphene.Structs.Vec2.Vec2'
    -> m Point
    -- ^ __Returns:__ the initialized point
pointInitFromVec2 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Point -> Vec2 -> m Point
pointInitFromVec2 Point
p Vec2
src = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Vec2
src' <- Vec2 -> IO (Ptr Vec2)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec2
src
    Ptr Point
result <- Ptr Point -> Ptr Vec2 -> IO (Ptr Point)
graphene_point_init_from_vec2 Ptr Point
p' Ptr Vec2
src'
    Text -> Ptr Point -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pointInitFromVec2" Ptr Point
result
    Point
result' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Point -> Point
Point) Ptr Point
result
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Vec2 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec2
src
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
result'

#if defined(ENABLE_OVERLOADING)
data PointInitFromVec2MethodInfo
instance (signature ~ (Graphene.Vec2.Vec2 -> m Point), MonadIO m) => O.OverloadedMethod PointInitFromVec2MethodInfo Point signature where
    overloadedMethod = pointInitFromVec2

instance O.OverloadedMethodInfo PointInitFromVec2MethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointInitFromVec2",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointInitFromVec2"
        })


#endif

-- method Point::interpolate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the linear interpolation factor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the interpolated\n  point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_interpolate" graphene_point_interpolate :: 
    Ptr Point ->                            -- a : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Point ->                            -- b : TInterface (Name {namespace = "Graphene", name = "Point"})
    CDouble ->                              -- factor : TBasicType TDouble
    Ptr Point ->                            -- res : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Linearly interpolates the coordinates of /@a@/ and /@b@/ using the
-- given /@factor@/.
-- 
-- /Since: 1.0/
pointInterpolate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@a@/: a t'GI.Graphene.Structs.Point.Point'
    -> Point
    -- ^ /@b@/: a t'GI.Graphene.Structs.Point.Point'
    -> Double
    -- ^ /@factor@/: the linear interpolation factor
    -> m (Point)
pointInterpolate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Point -> Point -> Double -> m Point
pointInterpolate Point
a Point
b Double
factor = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
a' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
a
    Ptr Point
b' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
b
    let factor' :: CDouble
factor' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
factor
    Ptr Point
res <- Int -> IO (Ptr Point)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
8 :: IO (Ptr Point)
    Ptr Point -> Ptr Point -> CDouble -> Ptr Point -> IO ()
graphene_point_interpolate Ptr Point
a' Ptr Point
b' CDouble
factor' Ptr Point
res
    Point
res' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Point) Ptr Point
res
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
a
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
b
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
res'

#if defined(ENABLE_OVERLOADING)
data PointInterpolateMethodInfo
instance (signature ~ (Point -> Double -> m (Point)), MonadIO m) => O.OverloadedMethod PointInterpolateMethodInfo Point signature where
    overloadedMethod = pointInterpolate

instance O.OverloadedMethodInfo PointInterpolateMethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointInterpolate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointInterpolate"
        })


#endif

-- method Point::near
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "epsilon"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "threshold between the two points"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_near" graphene_point_near :: 
    Ptr Point ->                            -- a : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Point ->                            -- b : TInterface (Name {namespace = "Graphene", name = "Point"})
    CFloat ->                               -- epsilon : TBasicType TFloat
    IO CInt

-- | Checks whether the two points /@a@/ and /@b@/ are within
-- the threshold of /@epsilon@/.
-- 
-- /Since: 1.0/
pointNear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@a@/: a t'GI.Graphene.Structs.Point.Point'
    -> Point
    -- ^ /@b@/: a t'GI.Graphene.Structs.Point.Point'
    -> Float
    -- ^ /@epsilon@/: threshold between the two points
    -> m Bool
    -- ^ __Returns:__ @true@ if the distance is within /@epsilon@/
pointNear :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Point -> Point -> Float -> m Bool
pointNear Point
a Point
b Float
epsilon = 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 Point
a' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
a
    Ptr Point
b' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
b
    let epsilon' :: CFloat
epsilon' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
epsilon
    CInt
result <- Ptr Point -> Ptr Point -> CFloat -> IO CInt
graphene_point_near Ptr Point
a' Ptr Point
b' CFloat
epsilon'
    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
a
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
b
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PointNearMethodInfo
instance (signature ~ (Point -> Float -> m Bool), MonadIO m) => O.OverloadedMethod PointNearMethodInfo Point signature where
    overloadedMethod = pointNear

instance O.OverloadedMethodInfo PointNearMethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointNear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointNear"
        })


#endif

-- method Point::to_vec2
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec2" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the vertex"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_to_vec2" graphene_point_to_vec2 :: 
    Ptr Point ->                            -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Graphene.Vec2.Vec2 ->               -- v : TInterface (Name {namespace = "Graphene", name = "Vec2"})
    IO ()

-- | Stores the coordinates of the given t'GI.Graphene.Structs.Point.Point' into a
-- t'GI.Graphene.Structs.Vec2.Vec2'.
-- 
-- /Since: 1.4/
pointToVec2 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> m (Graphene.Vec2.Vec2)
pointToVec2 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Point -> m Vec2
pointToVec2 Point
p = IO Vec2 -> m Vec2
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec2 -> m Vec2) -> IO Vec2 -> m Vec2
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Vec2
v <- Int -> IO (Ptr Vec2)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Graphene.Vec2.Vec2)
    Ptr Point -> Ptr Vec2 -> IO ()
graphene_point_to_vec2 Ptr Point
p' Ptr Vec2
v
    Vec2
v' <- ((ManagedPtr Vec2 -> Vec2) -> Ptr Vec2 -> IO Vec2
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Vec2 -> Vec2
Graphene.Vec2.Vec2) Ptr Vec2
v
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Vec2 -> IO Vec2
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Vec2
v'

#if defined(ENABLE_OVERLOADING)
data PointToVec2MethodInfo
instance (signature ~ (m (Graphene.Vec2.Vec2)), MonadIO m) => O.OverloadedMethod PointToVec2MethodInfo Point signature where
    overloadedMethod = pointToVec2

instance O.OverloadedMethodInfo PointToVec2MethodInfo Point where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Graphene.Structs.Point.pointToVec2",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-graphene-1.0.5/docs/GI-Graphene-Structs-Point.html#v:pointToVec2"
        })


#endif

-- method Point::zero
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Point" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_point_zero" graphene_point_zero :: 
    IO (Ptr Point)

-- | Returns a point fixed at (0, 0).
-- 
-- /Since: 1.0/
pointZero ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Point
    -- ^ __Returns:__ a fixed point
pointZero :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Point
pointZero  = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Point
result <- IO (Ptr Point)
graphene_point_zero
    Text -> Ptr Point -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pointZero" Ptr Point
result
    Point
result' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Point -> Point
Point) Ptr Point
result
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolvePointMethod (t :: Symbol) (o :: *) :: * where
    ResolvePointMethod "distance" o = PointDistanceMethodInfo
    ResolvePointMethod "equal" o = PointEqualMethodInfo
    ResolvePointMethod "free" o = PointFreeMethodInfo
    ResolvePointMethod "init" o = PointInitMethodInfo
    ResolvePointMethod "initFromPoint" o = PointInitFromPointMethodInfo
    ResolvePointMethod "initFromVec2" o = PointInitFromVec2MethodInfo
    ResolvePointMethod "interpolate" o = PointInterpolateMethodInfo
    ResolvePointMethod "near" o = PointNearMethodInfo
    ResolvePointMethod "toVec2" o = PointToVec2MethodInfo
    ResolvePointMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePointMethod t Point, O.OverloadedMethod info Point p) => OL.IsLabel t (Point -> 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 ~ ResolvePointMethod t Point, O.OverloadedMethod info Point p, R.HasField t Point p) => R.HasField t Point p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolvePointMethod t Point, O.OverloadedMethodInfo info Point) => OL.IsLabel t (O.MethodProxy info Point) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif