{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkNumericSorter is a t'GI.Gtk.Objects.Sorter.Sorter' that compares numbers.
-- 
-- To obtain the numbers to compare, this sorter evaluates a t'GI.Gtk.Objects.Expression.Expression'.

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

module GI.Gtk.Objects.NumericSorter
    ( 

-- * Exported types
    NumericSorter(..)                       ,
    IsNumericSorter                         ,
    toNumericSorter                         ,


 -- * 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"), [changed]("GI.Gtk.Objects.Sorter#g:method:changed"), [compare]("GI.Gtk.Objects.Sorter#g:method:compare"), [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
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getExpression]("GI.Gtk.Objects.NumericSorter#g:method:getExpression"), [getOrder]("GI.Gtk.Objects.Sorter#g:method:getOrder"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSortOrder]("GI.Gtk.Objects.NumericSorter#g:method:getSortOrder").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setExpression]("GI.Gtk.Objects.NumericSorter#g:method:setExpression"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSortOrder]("GI.Gtk.Objects.NumericSorter#g:method:setSortOrder").

#if defined(ENABLE_OVERLOADING)
    ResolveNumericSorterMethod              ,
#endif

-- ** getExpression #method:getExpression#

#if defined(ENABLE_OVERLOADING)
    NumericSorterGetExpressionMethodInfo    ,
#endif
    numericSorterGetExpression              ,


-- ** getSortOrder #method:getSortOrder#

#if defined(ENABLE_OVERLOADING)
    NumericSorterGetSortOrderMethodInfo     ,
#endif
    numericSorterGetSortOrder               ,


-- ** new #method:new#

    numericSorterNew                        ,


-- ** setExpression #method:setExpression#

#if defined(ENABLE_OVERLOADING)
    NumericSorterSetExpressionMethodInfo    ,
#endif
    numericSorterSetExpression              ,


-- ** setSortOrder #method:setSortOrder#

#if defined(ENABLE_OVERLOADING)
    NumericSorterSetSortOrderMethodInfo     ,
#endif
    numericSorterSetSortOrder               ,




 -- * Properties


-- ** expression #attr:expression#
-- | The expression to evaluate on items to get a number to compare with

#if defined(ENABLE_OVERLOADING)
    NumericSorterExpressionPropertyInfo     ,
#endif
    clearNumericSorterExpression            ,
    constructNumericSorterExpression        ,
    getNumericSorterExpression              ,
#if defined(ENABLE_OVERLOADING)
    numericSorterExpression                 ,
#endif
    setNumericSorterExpression              ,


-- ** sortOrder #attr:sortOrder#
-- | Whether the sorter will sort smaller numbers first

#if defined(ENABLE_OVERLOADING)
    NumericSorterSortOrderPropertyInfo      ,
#endif
    constructNumericSorterSortOrder         ,
    getNumericSorterSortOrder               ,
#if defined(ENABLE_OVERLOADING)
    numericSorterSortOrder                  ,
#endif
    setNumericSorterSortOrder               ,




    ) 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.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.Expression as Gtk.Expression
import {-# SOURCE #-} qualified GI.Gtk.Objects.Sorter as Gtk.Sorter

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

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

foreign import ccall "gtk_numeric_sorter_get_type"
    c_gtk_numeric_sorter_get_type :: IO B.Types.GType

instance B.Types.TypedObject NumericSorter where
    glibType :: IO GType
glibType = IO GType
c_gtk_numeric_sorter_get_type

instance B.Types.GObject NumericSorter

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

instance O.HasParentTypes NumericSorter
type instance O.ParentTypes NumericSorter = '[Gtk.Sorter.Sorter, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveNumericSorterMethod (t :: Symbol) (o :: *) :: * where
    ResolveNumericSorterMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveNumericSorterMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveNumericSorterMethod "changed" o = Gtk.Sorter.SorterChangedMethodInfo
    ResolveNumericSorterMethod "compare" o = Gtk.Sorter.SorterCompareMethodInfo
    ResolveNumericSorterMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveNumericSorterMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveNumericSorterMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveNumericSorterMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveNumericSorterMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveNumericSorterMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveNumericSorterMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveNumericSorterMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveNumericSorterMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveNumericSorterMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveNumericSorterMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveNumericSorterMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveNumericSorterMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveNumericSorterMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveNumericSorterMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveNumericSorterMethod "getExpression" o = NumericSorterGetExpressionMethodInfo
    ResolveNumericSorterMethod "getOrder" o = Gtk.Sorter.SorterGetOrderMethodInfo
    ResolveNumericSorterMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveNumericSorterMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveNumericSorterMethod "getSortOrder" o = NumericSorterGetSortOrderMethodInfo
    ResolveNumericSorterMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveNumericSorterMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveNumericSorterMethod "setExpression" o = NumericSorterSetExpressionMethodInfo
    ResolveNumericSorterMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveNumericSorterMethod "setSortOrder" o = NumericSorterSetSortOrderMethodInfo
    ResolveNumericSorterMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "expression"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Expression"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@expression@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' numericSorter #expression
-- @
getNumericSorterExpression :: (MonadIO m, IsNumericSorter o) => o -> m (Maybe Gtk.Expression.Expression)
getNumericSorterExpression :: forall (m :: * -> *) o.
(MonadIO m, IsNumericSorter o) =>
o -> m (Maybe Expression)
getNumericSorterExpression o
obj = IO (Maybe Expression) -> m (Maybe Expression)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Expression) -> m (Maybe Expression))
-> IO (Maybe Expression) -> m (Maybe Expression)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Expression)
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
B.Properties.getObjectPropertyIsGValueInstance o
obj String
"expression"

-- | Set the value of the “@expression@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' numericSorter [ #expression 'Data.GI.Base.Attributes.:=' value ]
-- @
setNumericSorterExpression :: (MonadIO m, IsNumericSorter o, Gtk.Expression.IsExpression a) => o -> a -> m ()
setNumericSorterExpression :: forall (m :: * -> *) o a.
(MonadIO m, IsNumericSorter o, IsExpression a) =>
o -> a -> m ()
setNumericSorterExpression o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Expression
val' <- a -> IO Expression
forall (m :: * -> *) o.
(MonadIO m, IsExpression o) =>
o -> m Expression
Gtk.Expression.toExpression a
val
    o -> String -> Maybe Expression -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
B.Properties.setObjectPropertyIsGValueInstance o
obj String
"expression" (Expression -> Maybe Expression
forall a. a -> Maybe a
Just Expression
val')

-- | Construct a `GValueConstruct` with valid value for the “@expression@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructNumericSorterExpression :: (IsNumericSorter o, MIO.MonadIO m, Gtk.Expression.IsExpression a) => a -> m (GValueConstruct o)
constructNumericSorterExpression :: forall o (m :: * -> *) a.
(IsNumericSorter o, MonadIO m, IsExpression a) =>
a -> m (GValueConstruct o)
constructNumericSorterExpression a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    Expression
val' <- a -> IO Expression
forall (m :: * -> *) o.
(MonadIO m, IsExpression o) =>
o -> m Expression
Gtk.Expression.toExpression a
val
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Expression -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyIsGValueInstance String
"expression" (Expression -> Maybe Expression
forall a. a -> Maybe a
P.Just Expression
val')

-- | Set the value of the “@expression@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #expression
-- @
clearNumericSorterExpression :: (MonadIO m, IsNumericSorter o) => o -> m ()
clearNumericSorterExpression :: forall (m :: * -> *) o. (MonadIO m, IsNumericSorter o) => o -> m ()
clearNumericSorterExpression o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Expression -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
B.Properties.setObjectPropertyIsGValueInstance o
obj String
"expression" (Maybe Expression
forall a. Maybe a
Nothing :: Maybe Gtk.Expression.Expression)

#if defined(ENABLE_OVERLOADING)
data NumericSorterExpressionPropertyInfo
instance AttrInfo NumericSorterExpressionPropertyInfo where
    type AttrAllowedOps NumericSorterExpressionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint NumericSorterExpressionPropertyInfo = IsNumericSorter
    type AttrSetTypeConstraint NumericSorterExpressionPropertyInfo = (~) Gtk.Expression.Expression
    type AttrTransferTypeConstraint NumericSorterExpressionPropertyInfo = (~) Gtk.Expression.Expression
    type AttrTransferType NumericSorterExpressionPropertyInfo = Gtk.Expression.Expression
    type AttrGetType NumericSorterExpressionPropertyInfo = (Maybe Gtk.Expression.Expression)
    type AttrLabel NumericSorterExpressionPropertyInfo = "expression"
    type AttrOrigin NumericSorterExpressionPropertyInfo = NumericSorter
    attrGet = getNumericSorterExpression
    attrSet = setNumericSorterExpression
    attrTransfer _ v = do
        return v
    attrConstruct = constructNumericSorterExpression
    attrClear = clearNumericSorterExpression
#endif

-- VVV Prop "sort-order"
   -- Type: TInterface (Name {namespace = "Gtk", name = "SortType"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@sort-order@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' numericSorter #sortOrder
-- @
getNumericSorterSortOrder :: (MonadIO m, IsNumericSorter o) => o -> m Gtk.Enums.SortType
getNumericSorterSortOrder :: forall (m :: * -> *) o.
(MonadIO m, IsNumericSorter o) =>
o -> m SortType
getNumericSorterSortOrder o
obj = IO SortType -> m SortType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SortType -> m SortType) -> IO SortType -> m SortType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO SortType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"sort-order"

-- | Set the value of the “@sort-order@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' numericSorter [ #sortOrder 'Data.GI.Base.Attributes.:=' value ]
-- @
setNumericSorterSortOrder :: (MonadIO m, IsNumericSorter o) => o -> Gtk.Enums.SortType -> m ()
setNumericSorterSortOrder :: forall (m :: * -> *) o.
(MonadIO m, IsNumericSorter o) =>
o -> SortType -> m ()
setNumericSorterSortOrder o
obj SortType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> SortType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"sort-order" SortType
val

-- | Construct a `GValueConstruct` with valid value for the “@sort-order@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructNumericSorterSortOrder :: (IsNumericSorter o, MIO.MonadIO m) => Gtk.Enums.SortType -> m (GValueConstruct o)
constructNumericSorterSortOrder :: forall o (m :: * -> *).
(IsNumericSorter o, MonadIO m) =>
SortType -> m (GValueConstruct o)
constructNumericSorterSortOrder SortType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> SortType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"sort-order" SortType
val

#if defined(ENABLE_OVERLOADING)
data NumericSorterSortOrderPropertyInfo
instance AttrInfo NumericSorterSortOrderPropertyInfo where
    type AttrAllowedOps NumericSorterSortOrderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint NumericSorterSortOrderPropertyInfo = IsNumericSorter
    type AttrSetTypeConstraint NumericSorterSortOrderPropertyInfo = (~) Gtk.Enums.SortType
    type AttrTransferTypeConstraint NumericSorterSortOrderPropertyInfo = (~) Gtk.Enums.SortType
    type AttrTransferType NumericSorterSortOrderPropertyInfo = Gtk.Enums.SortType
    type AttrGetType NumericSorterSortOrderPropertyInfo = Gtk.Enums.SortType
    type AttrLabel NumericSorterSortOrderPropertyInfo = "sort-order"
    type AttrOrigin NumericSorterSortOrderPropertyInfo = NumericSorter
    attrGet = getNumericSorterSortOrder
    attrSet = setNumericSorterSortOrder
    attrTransfer _ v = do
        return v
    attrConstruct = constructNumericSorterSortOrder
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList NumericSorter
type instance O.AttributeList NumericSorter = NumericSorterAttributeList
type NumericSorterAttributeList = ('[ '("expression", NumericSorterExpressionPropertyInfo), '("sortOrder", NumericSorterSortOrderPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
numericSorterExpression :: AttrLabelProxy "expression"
numericSorterExpression = AttrLabelProxy

numericSorterSortOrder :: AttrLabelProxy "sortOrder"
numericSorterSortOrder = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList NumericSorter = NumericSorterSignalList
type NumericSorterSignalList = ('[ '("changed", Gtk.Sorter.SorterChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method NumericSorter::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "expression"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Expression" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The expression to evaluate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "NumericSorter" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_numeric_sorter_new" gtk_numeric_sorter_new :: 
    Ptr Gtk.Expression.Expression ->        -- expression : TInterface (Name {namespace = "Gtk", name = "Expression"})
    IO (Ptr NumericSorter)

-- | Creates a new numeric sorter using the given /@expression@/.
-- 
-- Smaller numbers will be sorted first. You can call
-- 'GI.Gtk.Objects.NumericSorter.numericSorterSetSortOrder' to change this.
numericSorterNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Expression.IsExpression a) =>
    Maybe (a)
    -- ^ /@expression@/: The expression to evaluate
    -> m NumericSorter
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.NumericSorter.NumericSorter'
numericSorterNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsExpression a) =>
Maybe a -> m NumericSorter
numericSorterNew Maybe a
expression = IO NumericSorter -> m NumericSorter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NumericSorter -> m NumericSorter)
-> IO NumericSorter -> m NumericSorter
forall a b. (a -> b) -> a -> b
$ do
    Ptr Expression
maybeExpression <- case Maybe a
expression of
        Maybe a
Nothing -> Ptr Expression -> IO (Ptr Expression)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
forall a. Ptr a
nullPtr
        Just a
jExpression -> do
            Ptr Expression
jExpression' <- a -> IO (Ptr Expression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
B.ManagedPtr.disownManagedPtr a
jExpression
            Ptr Expression -> IO (Ptr Expression)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
jExpression'
    Ptr NumericSorter
result <- Ptr Expression -> IO (Ptr NumericSorter)
gtk_numeric_sorter_new Ptr Expression
maybeExpression
    Text -> Ptr NumericSorter -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"numericSorterNew" Ptr NumericSorter
result
    NumericSorter
result' <- ((ManagedPtr NumericSorter -> NumericSorter)
-> Ptr NumericSorter -> IO NumericSorter
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr NumericSorter -> NumericSorter
NumericSorter) Ptr NumericSorter
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
expression a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    NumericSorter -> IO NumericSorter
forall (m :: * -> *) a. Monad m => a -> m a
return NumericSorter
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method NumericSorter::get_expression
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NumericSorter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkNumericSorter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Expression" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_numeric_sorter_get_expression" gtk_numeric_sorter_get_expression :: 
    Ptr NumericSorter ->                    -- self : TInterface (Name {namespace = "Gtk", name = "NumericSorter"})
    IO (Ptr Gtk.Expression.Expression)

-- | Gets the expression that is evaluated to obtain numbers from items.
numericSorterGetExpression ::
    (B.CallStack.HasCallStack, MonadIO m, IsNumericSorter a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NumericSorter.NumericSorter'
    -> m (Maybe Gtk.Expression.Expression)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.Expression.Expression', or 'P.Nothing'
numericSorterGetExpression :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumericSorter a) =>
a -> m (Maybe Expression)
numericSorterGetExpression a
self = IO (Maybe Expression) -> m (Maybe Expression)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Expression) -> m (Maybe Expression))
-> IO (Maybe Expression) -> m (Maybe Expression)
forall a b. (a -> b) -> a -> b
$ do
    Ptr NumericSorter
self' <- a -> IO (Ptr NumericSorter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Expression
result <- Ptr NumericSorter -> IO (Ptr Expression)
gtk_numeric_sorter_get_expression Ptr NumericSorter
self'
    Maybe Expression
maybeResult <- Ptr Expression
-> (Ptr Expression -> IO Expression) -> IO (Maybe Expression)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Expression
result ((Ptr Expression -> IO Expression) -> IO (Maybe Expression))
-> (Ptr Expression -> IO Expression) -> IO (Maybe Expression)
forall a b. (a -> b) -> a -> b
$ \Ptr Expression
result' -> do
        Expression
result'' <- ((ManagedPtr Expression -> Expression)
-> Ptr Expression -> IO Expression
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Expression -> Expression
Gtk.Expression.Expression) Ptr Expression
result'
        Expression -> IO Expression
forall (m :: * -> *) a. Monad m => a -> m a
return Expression
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Expression -> IO (Maybe Expression)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Expression
maybeResult

#if defined(ENABLE_OVERLOADING)
data NumericSorterGetExpressionMethodInfo
instance (signature ~ (m (Maybe Gtk.Expression.Expression)), MonadIO m, IsNumericSorter a) => O.OverloadedMethod NumericSorterGetExpressionMethodInfo a signature where
    overloadedMethod = numericSorterGetExpression

instance O.OverloadedMethodInfo NumericSorterGetExpressionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.NumericSorter.numericSorterGetExpression",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-NumericSorter.html#v:numericSorterGetExpression"
        }


#endif

-- method NumericSorter::get_sort_order
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NumericSorter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkNumericSorter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "SortType" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_numeric_sorter_get_sort_order" gtk_numeric_sorter_get_sort_order :: 
    Ptr NumericSorter ->                    -- self : TInterface (Name {namespace = "Gtk", name = "NumericSorter"})
    IO CUInt

-- | Gets whether this sorter will sort smaller numbers first.
numericSorterGetSortOrder ::
    (B.CallStack.HasCallStack, MonadIO m, IsNumericSorter a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NumericSorter.NumericSorter'
    -> m Gtk.Enums.SortType
    -- ^ __Returns:__ the order of the numbers
numericSorterGetSortOrder :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumericSorter a) =>
a -> m SortType
numericSorterGetSortOrder a
self = IO SortType -> m SortType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SortType -> m SortType) -> IO SortType -> m SortType
forall a b. (a -> b) -> a -> b
$ do
    Ptr NumericSorter
self' <- a -> IO (Ptr NumericSorter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr NumericSorter -> IO CUInt
gtk_numeric_sorter_get_sort_order Ptr NumericSorter
self'
    let result' :: SortType
result' = (Int -> SortType
forall a. Enum a => Int -> a
toEnum (Int -> SortType) -> (CUInt -> Int) -> CUInt -> SortType
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
self
    SortType -> IO SortType
forall (m :: * -> *) a. Monad m => a -> m a
return SortType
result'

#if defined(ENABLE_OVERLOADING)
data NumericSorterGetSortOrderMethodInfo
instance (signature ~ (m Gtk.Enums.SortType), MonadIO m, IsNumericSorter a) => O.OverloadedMethod NumericSorterGetSortOrderMethodInfo a signature where
    overloadedMethod = numericSorterGetSortOrder

instance O.OverloadedMethodInfo NumericSorterGetSortOrderMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.NumericSorter.numericSorterGetSortOrder",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-NumericSorter.html#v:numericSorterGetSortOrder"
        }


#endif

-- method NumericSorter::set_expression
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NumericSorter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkNumericSorter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "expression"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Expression" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkExpression, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_numeric_sorter_set_expression" gtk_numeric_sorter_set_expression :: 
    Ptr NumericSorter ->                    -- self : TInterface (Name {namespace = "Gtk", name = "NumericSorter"})
    Ptr Gtk.Expression.Expression ->        -- expression : TInterface (Name {namespace = "Gtk", name = "Expression"})
    IO ()

-- | Sets the expression that is evaluated to obtain numbers from items.
-- 
-- Unless an expression is set on /@self@/, the sorter will always
-- compare items as invalid.
-- 
-- The expression must have a return type that can be compared
-- numerically, such as @/G_TYPE_INT/@ or @/G_TYPE_DOUBLE/@.
numericSorterSetExpression ::
    (B.CallStack.HasCallStack, MonadIO m, IsNumericSorter a, Gtk.Expression.IsExpression b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NumericSorter.NumericSorter'
    -> Maybe (b)
    -- ^ /@expression@/: a t'GI.Gtk.Objects.Expression.Expression', or 'P.Nothing'
    -> m ()
numericSorterSetExpression :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsNumericSorter a, IsExpression b) =>
a -> Maybe b -> m ()
numericSorterSetExpression a
self Maybe b
expression = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr NumericSorter
self' <- a -> IO (Ptr NumericSorter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Expression
maybeExpression <- case Maybe b
expression of
        Maybe b
Nothing -> Ptr Expression -> IO (Ptr Expression)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
forall a. Ptr a
nullPtr
        Just b
jExpression -> do
            Ptr Expression
jExpression' <- b -> IO (Ptr Expression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jExpression
            Ptr Expression -> IO (Ptr Expression)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
jExpression'
    Ptr NumericSorter -> Ptr Expression -> IO ()
gtk_numeric_sorter_set_expression Ptr NumericSorter
self' Ptr Expression
maybeExpression
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
expression b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NumericSorterSetExpressionMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsNumericSorter a, Gtk.Expression.IsExpression b) => O.OverloadedMethod NumericSorterSetExpressionMethodInfo a signature where
    overloadedMethod = numericSorterSetExpression

instance O.OverloadedMethodInfo NumericSorterSetExpressionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.NumericSorter.numericSorterSetExpression",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-NumericSorter.html#v:numericSorterSetExpression"
        }


#endif

-- method NumericSorter::set_sort_order
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NumericSorter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkNumericSorter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sort_order"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SortType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to sort smaller numbers first"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_numeric_sorter_set_sort_order" gtk_numeric_sorter_set_sort_order :: 
    Ptr NumericSorter ->                    -- self : TInterface (Name {namespace = "Gtk", name = "NumericSorter"})
    CUInt ->                                -- sort_order : TInterface (Name {namespace = "Gtk", name = "SortType"})
    IO ()

-- | Sets whether to sort smaller numbers before larger ones.
numericSorterSetSortOrder ::
    (B.CallStack.HasCallStack, MonadIO m, IsNumericSorter a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NumericSorter.NumericSorter'
    -> Gtk.Enums.SortType
    -- ^ /@sortOrder@/: whether to sort smaller numbers first
    -> m ()
numericSorterSetSortOrder :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumericSorter a) =>
a -> SortType -> m ()
numericSorterSetSortOrder a
self SortType
sortOrder = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr NumericSorter
self' <- a -> IO (Ptr NumericSorter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let sortOrder' :: CUInt
sortOrder' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (SortType -> Int) -> SortType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SortType -> Int
forall a. Enum a => a -> Int
fromEnum) SortType
sortOrder
    Ptr NumericSorter -> CUInt -> IO ()
gtk_numeric_sorter_set_sort_order Ptr NumericSorter
self' CUInt
sortOrder'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NumericSorterSetSortOrderMethodInfo
instance (signature ~ (Gtk.Enums.SortType -> m ()), MonadIO m, IsNumericSorter a) => O.OverloadedMethod NumericSorterSetSortOrderMethodInfo a signature where
    overloadedMethod = numericSorterSetSortOrder

instance O.OverloadedMethodInfo NumericSorterSetSortOrderMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.NumericSorter.numericSorterSetSortOrder",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-NumericSorter.html#v:numericSorterSetSortOrder"
        }


#endif