{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.Orientable
(
Orientable(..) ,
IsOrientable ,
toOrientable ,
#if defined(ENABLE_OVERLOADING)
ResolveOrientableMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
OrientableGetOrientationMethodInfo ,
#endif
orientableGetOrientation ,
#if defined(ENABLE_OVERLOADING)
OrientableSetOrientationMethodInfo ,
#endif
orientableSetOrientation ,
#if defined(ENABLE_OVERLOADING)
OrientableOrientationPropertyInfo ,
#endif
constructOrientableOrientation ,
getOrientableOrientation ,
#if defined(ENABLE_OVERLOADING)
orientableOrientation ,
#endif
setOrientableOrientation ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
newtype Orientable = Orientable (SP.ManagedPtr Orientable)
deriving (Orientable -> Orientable -> Bool
(Orientable -> Orientable -> Bool)
-> (Orientable -> Orientable -> Bool) -> Eq Orientable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Orientable -> Orientable -> Bool
== :: Orientable -> Orientable -> Bool
$c/= :: Orientable -> Orientable -> Bool
/= :: Orientable -> Orientable -> Bool
Eq)
instance SP.ManagedPtrNewtype Orientable where
toManagedPtr :: Orientable -> ManagedPtr Orientable
toManagedPtr (Orientable ManagedPtr Orientable
p) = ManagedPtr Orientable
p
foreign import ccall "gtk_orientable_get_type"
c_gtk_orientable_get_type :: IO B.Types.GType
instance B.Types.TypedObject Orientable where
glibType :: IO GType
glibType = IO GType
c_gtk_orientable_get_type
instance B.Types.GObject Orientable
class (SP.GObject o, O.IsDescendantOf Orientable o) => IsOrientable o
instance (SP.GObject o, O.IsDescendantOf Orientable o) => IsOrientable o
instance O.HasParentTypes Orientable
type instance O.ParentTypes Orientable = '[GObject.Object.Object]
toOrientable :: (MIO.MonadIO m, IsOrientable o) => o -> m Orientable
toOrientable :: forall (m :: * -> *) o.
(MonadIO m, IsOrientable o) =>
o -> m Orientable
toOrientable = IO Orientable -> m Orientable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Orientable -> m Orientable)
-> (o -> IO Orientable) -> o -> m Orientable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Orientable -> Orientable) -> o -> IO Orientable
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Orientable -> Orientable
Orientable
instance B.GValue.IsGValue (Maybe Orientable) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_orientable_get_type
gvalueSet_ :: Ptr GValue -> Maybe Orientable -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Orientable
P.Nothing = Ptr GValue -> Ptr Orientable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Orientable
forall a. Ptr a
FP.nullPtr :: FP.Ptr Orientable)
gvalueSet_ Ptr GValue
gv (P.Just Orientable
obj) = Orientable -> (Ptr Orientable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Orientable
obj (Ptr GValue -> Ptr Orientable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Orientable)
gvalueGet_ Ptr GValue
gv = do
Ptr Orientable
ptr <- Ptr GValue -> IO (Ptr Orientable)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Orientable)
if Ptr Orientable
ptr Ptr Orientable -> Ptr Orientable -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Orientable
forall a. Ptr a
FP.nullPtr
then Orientable -> Maybe Orientable
forall a. a -> Maybe a
P.Just (Orientable -> Maybe Orientable)
-> IO Orientable -> IO (Maybe Orientable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Orientable -> Orientable)
-> Ptr Orientable -> IO Orientable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Orientable -> Orientable
Orientable Ptr Orientable
ptr
else Maybe Orientable -> IO (Maybe Orientable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Orientable
forall a. Maybe a
P.Nothing
getOrientableOrientation :: (MonadIO m, IsOrientable o) => o -> m Gtk.Enums.Orientation
getOrientableOrientation :: forall (m :: * -> *) o.
(MonadIO m, IsOrientable o) =>
o -> m Orientation
getOrientableOrientation o
obj = IO Orientation -> m Orientation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Orientation -> m Orientation)
-> IO Orientation -> m Orientation
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Orientation
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"orientation"
setOrientableOrientation :: (MonadIO m, IsOrientable o) => o -> Gtk.Enums.Orientation -> m ()
setOrientableOrientation :: forall (m :: * -> *) o.
(MonadIO m, IsOrientable o) =>
o -> Orientation -> m ()
setOrientableOrientation o
obj Orientation
val = IO () -> m ()
forall a. IO a -> m a
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 -> Orientation -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"orientation" Orientation
val
constructOrientableOrientation :: (IsOrientable o, MIO.MonadIO m) => Gtk.Enums.Orientation -> m (GValueConstruct o)
constructOrientableOrientation :: forall o (m :: * -> *).
(IsOrientable o, MonadIO m) =>
Orientation -> m (GValueConstruct o)
constructOrientableOrientation Orientation
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Orientation -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"orientation" Orientation
val
#if defined(ENABLE_OVERLOADING)
data OrientableOrientationPropertyInfo
instance AttrInfo OrientableOrientationPropertyInfo where
type AttrAllowedOps OrientableOrientationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint OrientableOrientationPropertyInfo = IsOrientable
type AttrSetTypeConstraint OrientableOrientationPropertyInfo = (~) Gtk.Enums.Orientation
type AttrTransferTypeConstraint OrientableOrientationPropertyInfo = (~) Gtk.Enums.Orientation
type AttrTransferType OrientableOrientationPropertyInfo = Gtk.Enums.Orientation
type AttrGetType OrientableOrientationPropertyInfo = Gtk.Enums.Orientation
type AttrLabel OrientableOrientationPropertyInfo = "orientation"
type AttrOrigin OrientableOrientationPropertyInfo = Orientable
attrGet = getOrientableOrientation
attrSet = setOrientableOrientation
attrTransfer _ v = do
return v
attrConstruct = constructOrientableOrientation
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.Orientable.orientation"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Interfaces-Orientable.html#g:attr:orientation"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Orientable
type instance O.AttributeList Orientable = OrientableAttributeList
type OrientableAttributeList = ('[ '("orientation", OrientableOrientationPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
orientableOrientation :: AttrLabelProxy "orientation"
orientableOrientation = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveOrientableMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveOrientableMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveOrientableMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveOrientableMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveOrientableMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveOrientableMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveOrientableMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveOrientableMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveOrientableMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveOrientableMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveOrientableMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveOrientableMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveOrientableMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveOrientableMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveOrientableMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveOrientableMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveOrientableMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveOrientableMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveOrientableMethod "getOrientation" o = OrientableGetOrientationMethodInfo
ResolveOrientableMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveOrientableMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveOrientableMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveOrientableMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveOrientableMethod "setOrientation" o = OrientableSetOrientationMethodInfo
ResolveOrientableMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveOrientableMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveOrientableMethod t Orientable, O.OverloadedMethod info Orientable p) => OL.IsLabel t (Orientable -> 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 ~ ResolveOrientableMethod t Orientable, O.OverloadedMethod info Orientable p, R.HasField t Orientable p) => R.HasField t Orientable p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveOrientableMethod t Orientable, O.OverloadedMethodInfo info Orientable) => OL.IsLabel t (O.MethodProxy info Orientable) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "gtk_orientable_get_orientation" gtk_orientable_get_orientation ::
Ptr Orientable ->
IO CUInt
orientableGetOrientation ::
(B.CallStack.HasCallStack, MonadIO m, IsOrientable a) =>
a
-> m Gtk.Enums.Orientation
orientableGetOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOrientable a) =>
a -> m Orientation
orientableGetOrientation a
orientable = IO Orientation -> m Orientation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Orientation -> m Orientation)
-> IO Orientation -> m Orientation
forall a b. (a -> b) -> a -> b
$ do
Ptr Orientable
orientable' <- a -> IO (Ptr Orientable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
orientable
CUInt
result <- Ptr Orientable -> IO CUInt
gtk_orientable_get_orientation Ptr Orientable
orientable'
let result' :: Orientation
result' = (Int -> Orientation
forall a. Enum a => Int -> a
toEnum (Int -> Orientation) -> (CUInt -> Int) -> CUInt -> Orientation
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
orientable
Orientation -> IO Orientation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
result'
#if defined(ENABLE_OVERLOADING)
data OrientableGetOrientationMethodInfo
instance (signature ~ (m Gtk.Enums.Orientation), MonadIO m, IsOrientable a) => O.OverloadedMethod OrientableGetOrientationMethodInfo a signature where
overloadedMethod = orientableGetOrientation
instance O.OverloadedMethodInfo OrientableGetOrientationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.Orientable.orientableGetOrientation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Interfaces-Orientable.html#v:orientableGetOrientation"
})
#endif
foreign import ccall "gtk_orientable_set_orientation" gtk_orientable_set_orientation ::
Ptr Orientable ->
CUInt ->
IO ()
orientableSetOrientation ::
(B.CallStack.HasCallStack, MonadIO m, IsOrientable a) =>
a
-> Gtk.Enums.Orientation
-> m ()
orientableSetOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOrientable a) =>
a -> Orientation -> m ()
orientableSetOrientation a
orientable Orientation
orientation = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Orientable
orientable' <- a -> IO (Ptr Orientable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
orientable
let orientation' :: CUInt
orientation' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Orientation -> Int) -> Orientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Orientation -> Int
forall a. Enum a => a -> Int
fromEnum) Orientation
orientation
Ptr Orientable -> CUInt -> IO ()
gtk_orientable_set_orientation Ptr Orientable
orientable' CUInt
orientation'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
orientable
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data OrientableSetOrientationMethodInfo
instance (signature ~ (Gtk.Enums.Orientation -> m ()), MonadIO m, IsOrientable a) => O.OverloadedMethod OrientableSetOrientationMethodInfo a signature where
overloadedMethod = orientableSetOrientation
instance O.OverloadedMethodInfo OrientableSetOrientationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.Orientable.orientableSetOrientation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Interfaces-Orientable.html#v:orientableSetOrientation"
})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Orientable = OrientableSignalList
type OrientableSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif