{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.GdkX11.Objects.X11Cursor
    ( 

-- * Exported types
    X11Cursor(..)                           ,
    IsX11Cursor                             ,
    toX11Cursor                             ,
    noX11Cursor                             ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveX11CursorMethod                  ,
#endif


-- ** getXcursor #method:getXcursor#

#if defined(ENABLE_OVERLOADING)
    X11CursorGetXcursorMethodInfo           ,
#endif
    x11CursorGetXcursor                     ,


-- ** getXdisplay #method:getXdisplay#

#if defined(ENABLE_OVERLOADING)
    X11CursorGetXdisplayMethodInfo          ,
#endif
    x11CursorGetXdisplay                    ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Xlib.Structs.Display as Xlib.Display

-- | Memory-managed wrapper type.
newtype X11Cursor = X11Cursor (ManagedPtr X11Cursor)
    deriving (X11Cursor -> X11Cursor -> Bool
(X11Cursor -> X11Cursor -> Bool)
-> (X11Cursor -> X11Cursor -> Bool) -> Eq X11Cursor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: X11Cursor -> X11Cursor -> Bool
$c/= :: X11Cursor -> X11Cursor -> Bool
== :: X11Cursor -> X11Cursor -> Bool
$c== :: X11Cursor -> X11Cursor -> Bool
Eq)
foreign import ccall "gdk_x11_cursor_get_type"
    c_gdk_x11_cursor_get_type :: IO GType

instance GObject X11Cursor where
    gobjectType :: IO GType
gobjectType = IO GType
c_gdk_x11_cursor_get_type
    

-- | Convert 'X11Cursor' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue X11Cursor where
    toGValue :: X11Cursor -> IO GValue
toGValue o :: X11Cursor
o = do
        GType
gtype <- IO GType
c_gdk_x11_cursor_get_type
        X11Cursor -> (Ptr X11Cursor -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr X11Cursor
o (GType
-> (GValue -> Ptr X11Cursor -> IO ()) -> Ptr X11Cursor -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr X11Cursor -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO X11Cursor
fromGValue gv :: GValue
gv = do
        Ptr X11Cursor
ptr <- GValue -> IO (Ptr X11Cursor)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr X11Cursor)
        (ManagedPtr X11Cursor -> X11Cursor)
-> Ptr X11Cursor -> IO X11Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr X11Cursor -> X11Cursor
X11Cursor Ptr X11Cursor
ptr
        
    

-- | Type class for types which can be safely cast to `X11Cursor`, for instance with `toX11Cursor`.
class (GObject o, O.IsDescendantOf X11Cursor o) => IsX11Cursor o
instance (GObject o, O.IsDescendantOf X11Cursor o) => IsX11Cursor o

instance O.HasParentTypes X11Cursor
type instance O.ParentTypes X11Cursor = '[Gdk.Cursor.Cursor, GObject.Object.Object]

-- | Cast to `X11Cursor`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toX11Cursor :: (MonadIO m, IsX11Cursor o) => o -> m X11Cursor
toX11Cursor :: o -> m X11Cursor
toX11Cursor = IO X11Cursor -> m X11Cursor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO X11Cursor -> m X11Cursor)
-> (o -> IO X11Cursor) -> o -> m X11Cursor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr X11Cursor -> X11Cursor) -> o -> IO X11Cursor
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr X11Cursor -> X11Cursor
X11Cursor

-- | A convenience alias for `Nothing` :: `Maybe` `X11Cursor`.
noX11Cursor :: Maybe X11Cursor
noX11Cursor :: Maybe X11Cursor
noX11Cursor = Maybe X11Cursor
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveX11CursorMethod (t :: Symbol) (o :: *) :: * where
    ResolveX11CursorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveX11CursorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveX11CursorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveX11CursorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveX11CursorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveX11CursorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveX11CursorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveX11CursorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveX11CursorMethod "ref" o = Gdk.Cursor.CursorRefMethodInfo
    ResolveX11CursorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveX11CursorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveX11CursorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveX11CursorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveX11CursorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveX11CursorMethod "unref" o = Gdk.Cursor.CursorUnrefMethodInfo
    ResolveX11CursorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveX11CursorMethod "getCursorType" o = Gdk.Cursor.CursorGetCursorTypeMethodInfo
    ResolveX11CursorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveX11CursorMethod "getDisplay" o = Gdk.Cursor.CursorGetDisplayMethodInfo
    ResolveX11CursorMethod "getImage" o = Gdk.Cursor.CursorGetImageMethodInfo
    ResolveX11CursorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveX11CursorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveX11CursorMethod "getSurface" o = Gdk.Cursor.CursorGetSurfaceMethodInfo
    ResolveX11CursorMethod "getXcursor" o = X11CursorGetXcursorMethodInfo
    ResolveX11CursorMethod "getXdisplay" o = X11CursorGetXdisplayMethodInfo
    ResolveX11CursorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveX11CursorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveX11CursorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveX11CursorMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveX11CursorMethod t X11Cursor, O.MethodInfo info X11Cursor p) => OL.IsLabel t (X11Cursor -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList X11Cursor
type instance O.AttributeList X11Cursor = X11CursorAttributeList
type X11CursorAttributeList = ('[ '("cursorType", Gdk.Cursor.CursorCursorTypePropertyInfo), '("display", Gdk.Cursor.CursorDisplayPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList X11Cursor = X11CursorSignalList
type X11CursorSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method X11Cursor::get_xcursor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cursor"
--           , argType =
--               TInterface Name { namespace = "GdkX11" , name = "X11Cursor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkCursor." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TULong)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_x11_cursor_get_xcursor" gdk_x11_cursor_get_xcursor :: 
    Ptr X11Cursor ->                        -- cursor : TInterface (Name {namespace = "GdkX11", name = "X11Cursor"})
    IO CULong

-- | Returns the X cursor belonging to a t'GI.Gdk.Objects.Cursor.Cursor'.
x11CursorGetXcursor ::
    (B.CallStack.HasCallStack, MonadIO m, IsX11Cursor a) =>
    a
    -- ^ /@cursor@/: a t'GI.Gdk.Objects.Cursor.Cursor'.
    -> m CULong
    -- ^ __Returns:__ an Xlib Cursor.
x11CursorGetXcursor :: a -> m CULong
x11CursorGetXcursor cursor :: a
cursor = IO CULong -> m CULong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong
forall a b. (a -> b) -> a -> b
$ do
    Ptr X11Cursor
cursor' <- a -> IO (Ptr X11Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
    CULong
result <- Ptr X11Cursor -> IO CULong
gdk_x11_cursor_get_xcursor Ptr X11Cursor
cursor'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cursor
    CULong -> IO CULong
forall (m :: * -> *) a. Monad m => a -> m a
return CULong
result

#if defined(ENABLE_OVERLOADING)
data X11CursorGetXcursorMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsX11Cursor a) => O.MethodInfo X11CursorGetXcursorMethodInfo a signature where
    overloadedMethod = x11CursorGetXcursor

#endif

-- method X11Cursor::get_xdisplay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cursor"
--           , argType =
--               TInterface Name { namespace = "GdkX11" , name = "X11Cursor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkCursor." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "xlib" , name = "Display" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_x11_cursor_get_xdisplay" gdk_x11_cursor_get_xdisplay :: 
    Ptr X11Cursor ->                        -- cursor : TInterface (Name {namespace = "GdkX11", name = "X11Cursor"})
    IO (Ptr Xlib.Display.Display)

-- | Returns the display of a t'GI.Gdk.Objects.Cursor.Cursor'.
x11CursorGetXdisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsX11Cursor a) =>
    a
    -- ^ /@cursor@/: a t'GI.Gdk.Objects.Cursor.Cursor'.
    -> m Xlib.Display.Display
    -- ^ __Returns:__ an Xlib Display*.
x11CursorGetXdisplay :: a -> m Display
x11CursorGetXdisplay cursor :: a
cursor = IO Display -> m Display
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ do
    Ptr X11Cursor
cursor' <- a -> IO (Ptr X11Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cursor
    Ptr Display
result <- Ptr X11Cursor -> IO (Ptr Display)
gdk_x11_cursor_get_xdisplay Ptr X11Cursor
cursor'
    Text -> Ptr Display -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "x11CursorGetXdisplay" Ptr Display
result
    Display
result' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Display -> Display
Xlib.Display.Display) Ptr Display
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cursor
    Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result'

#if defined(ENABLE_OVERLOADING)
data X11CursorGetXdisplayMethodInfo
instance (signature ~ (m Xlib.Display.Display), MonadIO m, IsX11Cursor a) => O.MethodInfo X11CursorGetXdisplayMethodInfo a signature where
    overloadedMethod = x11CursorGetXdisplay

#endif