{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gdk.Objects.Visual.Visual' contains information about
-- a particular visual.

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

module GI.Gdk.Objects.Visual
    ( 

-- * Exported types
    Visual(..)                              ,
    IsVisual                                ,
    toVisual                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBitsPerRgb]("GI.Gdk.Objects.Visual#g:method:getBitsPerRgb"), [getBluePixelDetails]("GI.Gdk.Objects.Visual#g:method:getBluePixelDetails"), [getByteOrder]("GI.Gdk.Objects.Visual#g:method:getByteOrder"), [getColormapSize]("GI.Gdk.Objects.Visual#g:method:getColormapSize"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDepth]("GI.Gdk.Objects.Visual#g:method:getDepth"), [getGreenPixelDetails]("GI.Gdk.Objects.Visual#g:method:getGreenPixelDetails"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRedPixelDetails]("GI.Gdk.Objects.Visual#g:method:getRedPixelDetails"), [getScreen]("GI.Gdk.Objects.Visual#g:method:getScreen"), [getVisualType]("GI.Gdk.Objects.Visual#g:method:getVisualType").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveVisualMethod                     ,
#endif

-- ** getBest #method:getBest#

    visualGetBest                           ,


-- ** getBestDepth #method:getBestDepth#

    visualGetBestDepth                      ,


-- ** getBestType #method:getBestType#

    visualGetBestType                       ,


-- ** getBestWithBoth #method:getBestWithBoth#

    visualGetBestWithBoth                   ,


-- ** getBestWithDepth #method:getBestWithDepth#

    visualGetBestWithDepth                  ,


-- ** getBestWithType #method:getBestWithType#

    visualGetBestWithType                   ,


-- ** getBitsPerRgb #method:getBitsPerRgb#

#if defined(ENABLE_OVERLOADING)
    VisualGetBitsPerRgbMethodInfo           ,
#endif
    visualGetBitsPerRgb                     ,


-- ** getBluePixelDetails #method:getBluePixelDetails#

#if defined(ENABLE_OVERLOADING)
    VisualGetBluePixelDetailsMethodInfo     ,
#endif
    visualGetBluePixelDetails               ,


-- ** getByteOrder #method:getByteOrder#

#if defined(ENABLE_OVERLOADING)
    VisualGetByteOrderMethodInfo            ,
#endif
    visualGetByteOrder                      ,


-- ** getColormapSize #method:getColormapSize#

#if defined(ENABLE_OVERLOADING)
    VisualGetColormapSizeMethodInfo         ,
#endif
    visualGetColormapSize                   ,


-- ** getDepth #method:getDepth#

#if defined(ENABLE_OVERLOADING)
    VisualGetDepthMethodInfo                ,
#endif
    visualGetDepth                          ,


-- ** getGreenPixelDetails #method:getGreenPixelDetails#

#if defined(ENABLE_OVERLOADING)
    VisualGetGreenPixelDetailsMethodInfo    ,
#endif
    visualGetGreenPixelDetails              ,


-- ** getRedPixelDetails #method:getRedPixelDetails#

#if defined(ENABLE_OVERLOADING)
    VisualGetRedPixelDetailsMethodInfo      ,
#endif
    visualGetRedPixelDetails                ,


-- ** getScreen #method:getScreen#

#if defined(ENABLE_OVERLOADING)
    VisualGetScreenMethodInfo               ,
#endif
    visualGetScreen                         ,


-- ** getSystem #method:getSystem#

    visualGetSystem                         ,


-- ** getVisualType #method:getVisualType#

#if defined(ENABLE_OVERLOADING)
    VisualGetVisualTypeMethodInfo           ,
#endif
    visualGetVisualType                     ,




    ) 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.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.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 qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Screen as Gdk.Screen

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

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

foreign import ccall "gdk_visual_get_type"
    c_gdk_visual_get_type :: IO B.Types.GType

instance B.Types.TypedObject Visual where
    glibType :: IO GType
glibType = IO GType
c_gdk_visual_get_type

instance B.Types.GObject Visual

-- | Type class for types which can be safely cast to `Visual`, for instance with `toVisual`.
class (SP.GObject o, O.IsDescendantOf Visual o) => IsVisual o
instance (SP.GObject o, O.IsDescendantOf Visual o) => IsVisual o

instance O.HasParentTypes Visual
type instance O.ParentTypes Visual = '[GObject.Object.Object]

-- | Cast to `Visual`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toVisual :: (MIO.MonadIO m, IsVisual o) => o -> m Visual
toVisual :: forall (m :: * -> *) o. (MonadIO m, IsVisual o) => o -> m Visual
toVisual = IO Visual -> m Visual
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Visual -> m Visual) -> (o -> IO Visual) -> o -> m Visual
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Visual -> Visual) -> o -> IO Visual
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Visual -> Visual
Visual

-- | Convert 'Visual' 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 Visual) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_visual_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Visual -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Visual
P.Nothing = Ptr GValue -> Ptr Visual -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Visual
forall a. Ptr a
FP.nullPtr :: FP.Ptr Visual)
    gvalueSet_ Ptr GValue
gv (P.Just Visual
obj) = Visual -> (Ptr Visual -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Visual
obj (Ptr GValue -> Ptr Visual -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Visual)
gvalueGet_ Ptr GValue
gv = do
        Ptr Visual
ptr <- Ptr GValue -> IO (Ptr Visual)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Visual)
        if Ptr Visual
ptr Ptr Visual -> Ptr Visual -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Visual
forall a. Ptr a
FP.nullPtr
        then Visual -> Maybe Visual
forall a. a -> Maybe a
P.Just (Visual -> Maybe Visual) -> IO Visual -> IO (Maybe Visual)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Visual -> Visual) -> Ptr Visual -> IO Visual
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Visual -> Visual
Visual Ptr Visual
ptr
        else Maybe Visual -> IO (Maybe Visual)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Visual
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveVisualMethod (t :: Symbol) (o :: *) :: * where
    ResolveVisualMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveVisualMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveVisualMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveVisualMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveVisualMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveVisualMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveVisualMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveVisualMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveVisualMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveVisualMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveVisualMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveVisualMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveVisualMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveVisualMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveVisualMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveVisualMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveVisualMethod "getBitsPerRgb" o = VisualGetBitsPerRgbMethodInfo
    ResolveVisualMethod "getBluePixelDetails" o = VisualGetBluePixelDetailsMethodInfo
    ResolveVisualMethod "getByteOrder" o = VisualGetByteOrderMethodInfo
    ResolveVisualMethod "getColormapSize" o = VisualGetColormapSizeMethodInfo
    ResolveVisualMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveVisualMethod "getDepth" o = VisualGetDepthMethodInfo
    ResolveVisualMethod "getGreenPixelDetails" o = VisualGetGreenPixelDetailsMethodInfo
    ResolveVisualMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveVisualMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveVisualMethod "getRedPixelDetails" o = VisualGetRedPixelDetailsMethodInfo
    ResolveVisualMethod "getScreen" o = VisualGetScreenMethodInfo
    ResolveVisualMethod "getVisualType" o = VisualGetVisualTypeMethodInfo
    ResolveVisualMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveVisualMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveVisualMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveVisualMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Visual
type instance O.AttributeList Visual = VisualAttributeList
type VisualAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

foreign import ccall "gdk_visual_get_bits_per_rgb" gdk_visual_get_bits_per_rgb :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    IO Int32

{-# DEPRECATED visualGetBitsPerRgb ["(Since version 3.22.)","Use 'GI.Gdk.Objects.Visual.visualGetRedPixelDetails' and its variants to","    learn about the pixel layout of TrueColor and DirectColor visuals"] #-}
-- | Returns the number of significant bits per red, green and blue value.
-- 
-- Not all GDK backend provide a meaningful value for this function.
-- 
-- /Since: 2.22/
visualGetBitsPerRgb ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: a t'GI.Gdk.Objects.Visual.Visual'
    -> m Int32
    -- ^ __Returns:__ The number of significant bits per color value for /@visual@/.
visualGetBitsPerRgb :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m Int32
visualGetBitsPerRgb a
visual = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    Int32
result <- Ptr Visual -> IO Int32
gdk_visual_get_bits_per_rgb Ptr Visual
visual'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data VisualGetBitsPerRgbMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetBitsPerRgbMethodInfo a signature where
    overloadedMethod = visualGetBitsPerRgb

instance O.OverloadedMethodInfo VisualGetBitsPerRgbMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetBitsPerRgb",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetBitsPerRgb"
        }


#endif

-- method Visual::get_blue_pixel_details
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkVisual" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mask"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #guint32 to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "shift"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #gint to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "precision"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #gint to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_blue_pixel_details" gdk_visual_get_blue_pixel_details :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    Ptr Word32 ->                           -- mask : TBasicType TUInt32
    Ptr Int32 ->                            -- shift : TBasicType TInt
    Ptr Int32 ->                            -- precision : TBasicType TInt
    IO ()

-- | Obtains values that are needed to calculate blue pixel values in TrueColor
-- and DirectColor. The “mask” is the significant bits within the pixel.
-- The “shift” is the number of bits left we must shift a primary for it
-- to be in position (according to the \"mask\"). Finally, \"precision\" refers
-- to how much precision the pixel value contains for a particular primary.
-- 
-- /Since: 2.22/
visualGetBluePixelDetails ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: a t'GI.Gdk.Objects.Visual.Visual'
    -> m ((Word32, Int32, Int32))
visualGetBluePixelDetails :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m (Word32, Int32, Int32)
visualGetBluePixelDetails a
visual = IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32))
-> IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    Ptr Word32
mask <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr Int32
shift <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
precision <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Visual -> Ptr Word32 -> Ptr Int32 -> Ptr Int32 -> IO ()
gdk_visual_get_blue_pixel_details Ptr Visual
visual' Ptr Word32
mask Ptr Int32
shift Ptr Int32
precision
    Word32
mask' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
mask
    Int32
shift' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
shift
    Int32
precision' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
precision
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
mask
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
shift
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
precision
    (Word32, Int32, Int32) -> IO (Word32, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
mask', Int32
shift', Int32
precision')

#if defined(ENABLE_OVERLOADING)
data VisualGetBluePixelDetailsMethodInfo
instance (signature ~ (m ((Word32, Int32, Int32))), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetBluePixelDetailsMethodInfo a signature where
    overloadedMethod = visualGetBluePixelDetails

instance O.OverloadedMethodInfo VisualGetBluePixelDetailsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetBluePixelDetails",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetBluePixelDetails"
        }


#endif

-- method Visual::get_byte_order
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GdkVisual." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "ByteOrder" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_byte_order" gdk_visual_get_byte_order :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    IO CUInt

{-# DEPRECATED visualGetByteOrder ["(Since version 3.22)","This information is not useful"] #-}
-- | Returns the byte order of this visual.
-- 
-- The information returned by this function is only relevant
-- when working with XImages, and not all backends return
-- meaningful information for this.
-- 
-- /Since: 2.22/
visualGetByteOrder ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: A t'GI.Gdk.Objects.Visual.Visual'.
    -> m Gdk.Enums.ByteOrder
    -- ^ __Returns:__ A t'GI.Gdk.Enums.ByteOrder' stating the byte order of /@visual@/.
visualGetByteOrder :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m ByteOrder
visualGetByteOrder a
visual = IO ByteOrder -> m ByteOrder
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteOrder -> m ByteOrder) -> IO ByteOrder -> m ByteOrder
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    CUInt
result <- Ptr Visual -> IO CUInt
gdk_visual_get_byte_order Ptr Visual
visual'
    let result' :: ByteOrder
result' = (Int -> ByteOrder
forall a. Enum a => Int -> a
toEnum (Int -> ByteOrder) -> (CUInt -> Int) -> CUInt -> ByteOrder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    ByteOrder -> IO ByteOrder
forall (m :: * -> *) a. Monad m => a -> m a
return ByteOrder
result'

#if defined(ENABLE_OVERLOADING)
data VisualGetByteOrderMethodInfo
instance (signature ~ (m Gdk.Enums.ByteOrder), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetByteOrderMethodInfo a signature where
    overloadedMethod = visualGetByteOrder

instance O.OverloadedMethodInfo VisualGetByteOrderMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetByteOrder",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetByteOrder"
        }


#endif

-- method Visual::get_colormap_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GdkVisual." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_colormap_size" gdk_visual_get_colormap_size :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    IO Int32

{-# DEPRECATED visualGetColormapSize ["(Since version 3.22)","This information is not useful, since GDK does not","    provide APIs to operate on colormaps."] #-}
-- | Returns the size of a colormap for this visual.
-- 
-- You have to use platform-specific APIs to manipulate colormaps.
-- 
-- /Since: 2.22/
visualGetColormapSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: A t'GI.Gdk.Objects.Visual.Visual'.
    -> m Int32
    -- ^ __Returns:__ The size of a colormap that is suitable for /@visual@/.
visualGetColormapSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m Int32
visualGetColormapSize a
visual = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    Int32
result <- Ptr Visual -> IO Int32
gdk_visual_get_colormap_size Ptr Visual
visual'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data VisualGetColormapSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetColormapSizeMethodInfo a signature where
    overloadedMethod = visualGetColormapSize

instance O.OverloadedMethodInfo VisualGetColormapSizeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetColormapSize",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetColormapSize"
        }


#endif

-- method Visual::get_depth
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GdkVisual." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_depth" gdk_visual_get_depth :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    IO Int32

-- | Returns the bit depth of this visual.
-- 
-- /Since: 2.22/
visualGetDepth ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: A t'GI.Gdk.Objects.Visual.Visual'.
    -> m Int32
    -- ^ __Returns:__ The bit depth of this visual.
visualGetDepth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m Int32
visualGetDepth a
visual = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    Int32
result <- Ptr Visual -> IO Int32
gdk_visual_get_depth Ptr Visual
visual'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data VisualGetDepthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetDepthMethodInfo a signature where
    overloadedMethod = visualGetDepth

instance O.OverloadedMethodInfo VisualGetDepthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetDepth",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetDepth"
        }


#endif

-- method Visual::get_green_pixel_details
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkVisual" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mask"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #guint32 to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "shift"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #gint to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "precision"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #gint to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_green_pixel_details" gdk_visual_get_green_pixel_details :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    Ptr Word32 ->                           -- mask : TBasicType TUInt32
    Ptr Int32 ->                            -- shift : TBasicType TInt
    Ptr Int32 ->                            -- precision : TBasicType TInt
    IO ()

-- | Obtains values that are needed to calculate green pixel values in TrueColor
-- and DirectColor. The “mask” is the significant bits within the pixel.
-- The “shift” is the number of bits left we must shift a primary for it
-- to be in position (according to the \"mask\"). Finally, \"precision\" refers
-- to how much precision the pixel value contains for a particular primary.
-- 
-- /Since: 2.22/
visualGetGreenPixelDetails ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: a t'GI.Gdk.Objects.Visual.Visual'
    -> m ((Word32, Int32, Int32))
visualGetGreenPixelDetails :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m (Word32, Int32, Int32)
visualGetGreenPixelDetails a
visual = IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32))
-> IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    Ptr Word32
mask <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr Int32
shift <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
precision <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Visual -> Ptr Word32 -> Ptr Int32 -> Ptr Int32 -> IO ()
gdk_visual_get_green_pixel_details Ptr Visual
visual' Ptr Word32
mask Ptr Int32
shift Ptr Int32
precision
    Word32
mask' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
mask
    Int32
shift' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
shift
    Int32
precision' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
precision
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
mask
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
shift
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
precision
    (Word32, Int32, Int32) -> IO (Word32, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
mask', Int32
shift', Int32
precision')

#if defined(ENABLE_OVERLOADING)
data VisualGetGreenPixelDetailsMethodInfo
instance (signature ~ (m ((Word32, Int32, Int32))), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetGreenPixelDetailsMethodInfo a signature where
    overloadedMethod = visualGetGreenPixelDetails

instance O.OverloadedMethodInfo VisualGetGreenPixelDetailsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetGreenPixelDetails",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetGreenPixelDetails"
        }


#endif

-- method Visual::get_red_pixel_details
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GdkVisual" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mask"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #guint32 to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "shift"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #gint to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "precision"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to a #gint to be filled in, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_red_pixel_details" gdk_visual_get_red_pixel_details :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    Ptr Word32 ->                           -- mask : TBasicType TUInt32
    Ptr Int32 ->                            -- shift : TBasicType TInt
    Ptr Int32 ->                            -- precision : TBasicType TInt
    IO ()

-- | Obtains values that are needed to calculate red pixel values in TrueColor
-- and DirectColor. The “mask” is the significant bits within the pixel.
-- The “shift” is the number of bits left we must shift a primary for it
-- to be in position (according to the \"mask\"). Finally, \"precision\" refers
-- to how much precision the pixel value contains for a particular primary.
-- 
-- /Since: 2.22/
visualGetRedPixelDetails ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: A t'GI.Gdk.Objects.Visual.Visual'
    -> m ((Word32, Int32, Int32))
visualGetRedPixelDetails :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m (Word32, Int32, Int32)
visualGetRedPixelDetails a
visual = IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32))
-> IO (Word32, Int32, Int32) -> m (Word32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    Ptr Word32
mask <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr Int32
shift <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
precision <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Visual -> Ptr Word32 -> Ptr Int32 -> Ptr Int32 -> IO ()
gdk_visual_get_red_pixel_details Ptr Visual
visual' Ptr Word32
mask Ptr Int32
shift Ptr Int32
precision
    Word32
mask' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
mask
    Int32
shift' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
shift
    Int32
precision' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
precision
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
mask
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
shift
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
precision
    (Word32, Int32, Int32) -> IO (Word32, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
mask', Int32
shift', Int32
precision')

#if defined(ENABLE_OVERLOADING)
data VisualGetRedPixelDetailsMethodInfo
instance (signature ~ (m ((Word32, Int32, Int32))), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetRedPixelDetailsMethodInfo a signature where
    overloadedMethod = visualGetRedPixelDetails

instance O.OverloadedMethodInfo VisualGetRedPixelDetailsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetRedPixelDetails",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetRedPixelDetails"
        }


#endif

-- method Visual::get_screen
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkVisual" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Screen" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_screen" gdk_visual_get_screen :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    IO (Ptr Gdk.Screen.Screen)

-- | Gets the screen to which this visual belongs
-- 
-- /Since: 2.2/
visualGetScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: a t'GI.Gdk.Objects.Visual.Visual'
    -> m Gdk.Screen.Screen
    -- ^ __Returns:__ the screen to which this visual belongs.
visualGetScreen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m Screen
visualGetScreen a
visual = IO Screen -> m Screen
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Screen -> m Screen) -> IO Screen -> m Screen
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    Ptr Screen
result <- Ptr Visual -> IO (Ptr Screen)
gdk_visual_get_screen Ptr Visual
visual'
    Text -> Ptr Screen -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"visualGetScreen" Ptr Screen
result
    Screen
result' <- ((ManagedPtr Screen -> Screen) -> Ptr Screen -> IO Screen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Screen -> Screen
Gdk.Screen.Screen) Ptr Screen
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    Screen -> IO Screen
forall (m :: * -> *) a. Monad m => a -> m a
return Screen
result'

#if defined(ENABLE_OVERLOADING)
data VisualGetScreenMethodInfo
instance (signature ~ (m Gdk.Screen.Screen), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetScreenMethodInfo a signature where
    overloadedMethod = visualGetScreen

instance O.OverloadedMethodInfo VisualGetScreenMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetScreen",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetScreen"
        }


#endif

-- method Visual::get_visual_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "visual"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Visual" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GdkVisual." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "VisualType" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_visual_type" gdk_visual_get_visual_type :: 
    Ptr Visual ->                           -- visual : TInterface (Name {namespace = "Gdk", name = "Visual"})
    IO CUInt

-- | Returns the type of visual this is (PseudoColor, TrueColor, etc).
-- 
-- /Since: 2.22/
visualGetVisualType ::
    (B.CallStack.HasCallStack, MonadIO m, IsVisual a) =>
    a
    -- ^ /@visual@/: A t'GI.Gdk.Objects.Visual.Visual'.
    -> m Gdk.Enums.VisualType
    -- ^ __Returns:__ A t'GI.Gdk.Enums.VisualType' stating the type of /@visual@/.
visualGetVisualType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVisual a) =>
a -> m VisualType
visualGetVisualType a
visual = IO VisualType -> m VisualType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VisualType -> m VisualType) -> IO VisualType -> m VisualType
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
visual' <- a -> IO (Ptr Visual)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
visual
    CUInt
result <- Ptr Visual -> IO CUInt
gdk_visual_get_visual_type Ptr Visual
visual'
    let result' :: VisualType
result' = (Int -> VisualType
forall a. Enum a => Int -> a
toEnum (Int -> VisualType) -> (CUInt -> Int) -> CUInt -> VisualType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
visual
    VisualType -> IO VisualType
forall (m :: * -> *) a. Monad m => a -> m a
return VisualType
result'

#if defined(ENABLE_OVERLOADING)
data VisualGetVisualTypeMethodInfo
instance (signature ~ (m Gdk.Enums.VisualType), MonadIO m, IsVisual a) => O.OverloadedMethod VisualGetVisualTypeMethodInfo a signature where
    overloadedMethod = visualGetVisualType

instance O.OverloadedMethodInfo VisualGetVisualTypeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.Visual.visualGetVisualType",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-3.0.24/docs/GI-Gdk-Objects-Visual.html#v:visualGetVisualType"
        }


#endif

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

foreign import ccall "gdk_visual_get_best" gdk_visual_get_best :: 
    IO (Ptr Visual)

{-# DEPRECATED visualGetBest ["(Since version 3.22)","Visual selection should be done using","    'GI.Gdk.Objects.Screen.screenGetSystemVisual' and 'GI.Gdk.Objects.Screen.screenGetRgbaVisual'"] #-}
-- | Get the visual with the most available colors for the default
-- GDK screen. The return value should not be freed.
visualGetBest ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Visual
    -- ^ __Returns:__ best visual
visualGetBest :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Visual
visualGetBest  = IO Visual -> m Visual
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Visual -> m Visual) -> IO Visual -> m Visual
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
result <- IO (Ptr Visual)
gdk_visual_get_best
    Text -> Ptr Visual -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"visualGetBest" Ptr Visual
result
    Visual
result' <- ((ManagedPtr Visual -> Visual) -> Ptr Visual -> IO Visual
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Visual -> Visual
Visual) Ptr Visual
result
    Visual -> IO Visual
forall (m :: * -> *) a. Monad m => a -> m a
return Visual
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Visual::get_best_depth
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_best_depth" gdk_visual_get_best_depth :: 
    IO Int32

{-# DEPRECATED visualGetBestDepth ["(Since version 3.22)","Visual selection should be done using","    'GI.Gdk.Objects.Screen.screenGetSystemVisual' and 'GI.Gdk.Objects.Screen.screenGetRgbaVisual'"] #-}
-- | Get the best available depth for the default GDK screen.  “Best”
-- means “largest,” i.e. 32 preferred over 24 preferred over 8 bits
-- per pixel.
visualGetBestDepth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Int32
    -- ^ __Returns:__ best available depth
visualGetBestDepth :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Int32
visualGetBestDepth  = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Int32
result <- IO Int32
gdk_visual_get_best_depth
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Visual::get_best_type
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "VisualType" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_best_type" gdk_visual_get_best_type :: 
    IO CUInt

{-# DEPRECATED visualGetBestType ["(Since version 3.22)","Visual selection should be done using","    'GI.Gdk.Objects.Screen.screenGetSystemVisual' and 'GI.Gdk.Objects.Screen.screenGetRgbaVisual'"] #-}
-- | Return the best available visual type for the default GDK screen.
visualGetBestType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Gdk.Enums.VisualType
    -- ^ __Returns:__ best visual type
visualGetBestType :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m VisualType
visualGetBestType  = IO VisualType -> m VisualType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VisualType -> m VisualType) -> IO VisualType -> m VisualType
forall a b. (a -> b) -> a -> b
$ do
    CUInt
result <- IO CUInt
gdk_visual_get_best_type
    let result' :: VisualType
result' = (Int -> VisualType
forall a. Enum a => Int -> a
toEnum (Int -> VisualType) -> (CUInt -> Int) -> CUInt -> VisualType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    VisualType -> IO VisualType
forall (m :: * -> *) a. Monad m => a -> m a
return VisualType
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Visual::get_best_with_both
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "depth"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a bit depth" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "visual_type"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "VisualType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a visual type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Visual" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_best_with_both" gdk_visual_get_best_with_both :: 
    Int32 ->                                -- depth : TBasicType TInt
    CUInt ->                                -- visual_type : TInterface (Name {namespace = "Gdk", name = "VisualType"})
    IO (Ptr Visual)

{-# DEPRECATED visualGetBestWithBoth ["(Since version 3.22)","Visual selection should be done using","    'GI.Gdk.Objects.Screen.screenGetSystemVisual' and 'GI.Gdk.Objects.Screen.screenGetRgbaVisual'"] #-}
-- | Combines 'GI.Gdk.Objects.Visual.visualGetBestWithDepth' and
-- 'GI.Gdk.Objects.Visual.visualGetBestWithType'.
visualGetBestWithBoth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@depth@/: a bit depth
    -> Gdk.Enums.VisualType
    -- ^ /@visualType@/: a visual type
    -> m (Maybe Visual)
    -- ^ __Returns:__ best visual with both /@depth@/
    --     and /@visualType@/, or 'P.Nothing' if none
visualGetBestWithBoth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int32 -> VisualType -> m (Maybe Visual)
visualGetBestWithBoth Int32
depth VisualType
visualType = IO (Maybe Visual) -> m (Maybe Visual)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Visual) -> m (Maybe Visual))
-> IO (Maybe Visual) -> m (Maybe Visual)
forall a b. (a -> b) -> a -> b
$ do
    let visualType' :: CUInt
visualType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (VisualType -> Int) -> VisualType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VisualType -> Int
forall a. Enum a => a -> Int
fromEnum) VisualType
visualType
    Ptr Visual
result <- Int32 -> CUInt -> IO (Ptr Visual)
gdk_visual_get_best_with_both Int32
depth CUInt
visualType'
    Maybe Visual
maybeResult <- Ptr Visual -> (Ptr Visual -> IO Visual) -> IO (Maybe Visual)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Visual
result ((Ptr Visual -> IO Visual) -> IO (Maybe Visual))
-> (Ptr Visual -> IO Visual) -> IO (Maybe Visual)
forall a b. (a -> b) -> a -> b
$ \Ptr Visual
result' -> do
        Visual
result'' <- ((ManagedPtr Visual -> Visual) -> Ptr Visual -> IO Visual
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Visual -> Visual
Visual) Ptr Visual
result'
        Visual -> IO Visual
forall (m :: * -> *) a. Monad m => a -> m a
return Visual
result''
    Maybe Visual -> IO (Maybe Visual)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Visual
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method Visual::get_best_with_depth
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "depth"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a bit depth" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Visual" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_best_with_depth" gdk_visual_get_best_with_depth :: 
    Int32 ->                                -- depth : TBasicType TInt
    IO (Ptr Visual)

{-# DEPRECATED visualGetBestWithDepth ["(Since version 3.22)","Visual selection should be done using","    'GI.Gdk.Objects.Screen.screenGetSystemVisual' and 'GI.Gdk.Objects.Screen.screenGetRgbaVisual'"] #-}
-- | Get the best visual with depth /@depth@/ for the default GDK screen.
-- Color visuals and visuals with mutable colormaps are preferred
-- over grayscale or fixed-colormap visuals. The return value should
-- not be freed. 'P.Nothing' may be returned if no visual supports /@depth@/.
visualGetBestWithDepth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@depth@/: a bit depth
    -> m Visual
    -- ^ __Returns:__ best visual for the given depth
visualGetBestWithDepth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int32 -> m Visual
visualGetBestWithDepth Int32
depth = IO Visual -> m Visual
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Visual -> m Visual) -> IO Visual -> m Visual
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
result <- Int32 -> IO (Ptr Visual)
gdk_visual_get_best_with_depth Int32
depth
    Text -> Ptr Visual -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"visualGetBestWithDepth" Ptr Visual
result
    Visual
result' <- ((ManagedPtr Visual -> Visual) -> Ptr Visual -> IO Visual
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Visual -> Visual
Visual) Ptr Visual
result
    Visual -> IO Visual
forall (m :: * -> *) a. Monad m => a -> m a
return Visual
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Visual::get_best_with_type
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "visual_type"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "VisualType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a visual type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Visual" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_visual_get_best_with_type" gdk_visual_get_best_with_type :: 
    CUInt ->                                -- visual_type : TInterface (Name {namespace = "Gdk", name = "VisualType"})
    IO (Ptr Visual)

{-# DEPRECATED visualGetBestWithType ["(Since version 3.22)","Visual selection should be done using","    'GI.Gdk.Objects.Screen.screenGetSystemVisual' and 'GI.Gdk.Objects.Screen.screenGetRgbaVisual'"] #-}
-- | Get the best visual of the given /@visualType@/ for the default GDK screen.
-- Visuals with higher color depths are considered better. The return value
-- should not be freed. 'P.Nothing' may be returned if no visual has type
-- /@visualType@/.
visualGetBestWithType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gdk.Enums.VisualType
    -- ^ /@visualType@/: a visual type
    -> m Visual
    -- ^ __Returns:__ best visual of the given type
visualGetBestWithType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
VisualType -> m Visual
visualGetBestWithType VisualType
visualType = IO Visual -> m Visual
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Visual -> m Visual) -> IO Visual -> m Visual
forall a b. (a -> b) -> a -> b
$ do
    let visualType' :: CUInt
visualType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (VisualType -> Int) -> VisualType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VisualType -> Int
forall a. Enum a => a -> Int
fromEnum) VisualType
visualType
    Ptr Visual
result <- CUInt -> IO (Ptr Visual)
gdk_visual_get_best_with_type CUInt
visualType'
    Text -> Ptr Visual -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"visualGetBestWithType" Ptr Visual
result
    Visual
result' <- ((ManagedPtr Visual -> Visual) -> Ptr Visual -> IO Visual
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Visual -> Visual
Visual) Ptr Visual
result
    Visual -> IO Visual
forall (m :: * -> *) a. Monad m => a -> m a
return Visual
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gdk_visual_get_system" gdk_visual_get_system :: 
    IO (Ptr Visual)

{-# DEPRECATED visualGetSystem ["(Since version 3.22)","Use gdk_screen_get_system_visual (gdk_screen_get_default ())."] #-}
-- | Get the system’s default visual for the default GDK screen.
-- This is the visual for the root window of the display.
-- The return value should not be freed.
visualGetSystem ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Visual
    -- ^ __Returns:__ system visual
visualGetSystem :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Visual
visualGetSystem  = IO Visual -> m Visual
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Visual -> m Visual) -> IO Visual -> m Visual
forall a b. (a -> b) -> a -> b
$ do
    Ptr Visual
result <- IO (Ptr Visual)
gdk_visual_get_system
    Text -> Ptr Visual -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"visualGetSystem" Ptr Visual
result
    Visual
result' <- ((ManagedPtr Visual -> Visual) -> Ptr Visual -> IO Visual
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Visual -> Visual
Visual) Ptr Visual
result
    Visual -> IO Visual
forall (m :: * -> *) a. Monad m => a -> m a
return Visual
result'

#if defined(ENABLE_OVERLOADING)
#endif