{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.Icon
(
Icon(..) ,
IsIcon ,
toIcon ,
#if defined(ENABLE_OVERLOADING)
ResolveIconMethod ,
#endif
iconDeserialize ,
#if defined(ENABLE_OVERLOADING)
IconEqualMethodInfo ,
#endif
iconEqual ,
iconHash ,
iconNewForString ,
#if defined(ENABLE_OVERLOADING)
IconSerializeMethodInfo ,
#endif
iconSerialize ,
#if defined(ENABLE_OVERLOADING)
IconToStringMethodInfo ,
#endif
iconToString ,
) 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.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 GI.GObject.Objects.Object as GObject.Object
newtype Icon = Icon (SP.ManagedPtr Icon)
deriving (Icon -> Icon -> Bool
(Icon -> Icon -> Bool) -> (Icon -> Icon -> Bool) -> Eq Icon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Icon -> Icon -> Bool
$c/= :: Icon -> Icon -> Bool
== :: Icon -> Icon -> Bool
$c== :: Icon -> Icon -> Bool
Eq)
instance SP.ManagedPtrNewtype Icon where
toManagedPtr :: Icon -> ManagedPtr Icon
toManagedPtr (Icon ManagedPtr Icon
p) = ManagedPtr Icon
p
foreign import ccall "g_icon_get_type"
c_g_icon_get_type :: IO B.Types.GType
instance B.Types.TypedObject Icon where
glibType :: IO GType
glibType = IO GType
c_g_icon_get_type
instance B.Types.GObject Icon
instance B.GValue.IsGValue Icon where
toGValue :: Icon -> IO GValue
toGValue Icon
o = do
GType
gtype <- IO GType
c_g_icon_get_type
Icon -> (Ptr Icon -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Icon
o (GType -> (GValue -> Ptr Icon -> IO ()) -> Ptr Icon -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Icon -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Icon
fromGValue GValue
gv = do
Ptr Icon
ptr <- GValue -> IO (Ptr Icon)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Icon)
(ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Icon -> Icon
Icon Ptr Icon
ptr
class (SP.GObject o, O.IsDescendantOf Icon o) => IsIcon o
instance (SP.GObject o, O.IsDescendantOf Icon o) => IsIcon o
instance O.HasParentTypes Icon
type instance O.ParentTypes Icon = '[GObject.Object.Object]
toIcon :: (MonadIO m, IsIcon o) => o -> m Icon
toIcon :: o -> m Icon
toIcon = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> (o -> IO Icon) -> o -> m Icon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Icon -> Icon) -> o -> IO Icon
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Icon -> Icon
Icon
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Icon
type instance O.AttributeList Icon = IconAttributeList
type IconAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveIconMethod (t :: Symbol) (o :: *) :: * where
ResolveIconMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveIconMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveIconMethod "equal" o = IconEqualMethodInfo
ResolveIconMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveIconMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveIconMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveIconMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveIconMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveIconMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveIconMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveIconMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveIconMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveIconMethod "serialize" o = IconSerializeMethodInfo
ResolveIconMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveIconMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveIconMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveIconMethod "toString" o = IconToStringMethodInfo
ResolveIconMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveIconMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveIconMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveIconMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveIconMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveIconMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveIconMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveIconMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveIconMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIconMethod t Icon, O.MethodInfo info Icon p) => OL.IsLabel t (Icon -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_icon_equal" g_icon_equal ::
Ptr Icon ->
Ptr Icon ->
IO CInt
iconEqual ::
(B.CallStack.HasCallStack, MonadIO m, IsIcon a, IsIcon b) =>
a
-> Maybe (b)
-> m Bool
iconEqual :: a -> Maybe b -> m Bool
iconEqual a
icon1 Maybe b
icon2 = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Icon
icon1' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon1
Ptr Icon
maybeIcon2 <- case Maybe b
icon2 of
Maybe b
Nothing -> Ptr Icon -> IO (Ptr Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
forall a. Ptr a
nullPtr
Just b
jIcon2 -> do
Ptr Icon
jIcon2' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jIcon2
Ptr Icon -> IO (Ptr Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
jIcon2'
CInt
result <- Ptr Icon -> Ptr Icon -> IO CInt
g_icon_equal Ptr Icon
icon1' Ptr Icon
maybeIcon2
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon1
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
icon2 b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data IconEqualMethodInfo
instance (signature ~ (Maybe (b) -> m Bool), MonadIO m, IsIcon a, IsIcon b) => O.MethodInfo IconEqualMethodInfo a signature where
overloadedMethod = iconEqual
#endif
foreign import ccall "g_icon_serialize" g_icon_serialize ::
Ptr Icon ->
IO (Ptr GVariant)
iconSerialize ::
(B.CallStack.HasCallStack, MonadIO m, IsIcon a) =>
a
-> m GVariant
iconSerialize :: a -> m GVariant
iconSerialize a
icon = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
Ptr Icon
icon' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
Ptr GVariant
result <- Ptr Icon -> IO (Ptr GVariant)
g_icon_serialize Ptr Icon
icon'
Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSerialize" Ptr GVariant
result
GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
#if defined(ENABLE_OVERLOADING)
data IconSerializeMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsIcon a) => O.MethodInfo IconSerializeMethodInfo a signature where
overloadedMethod = iconSerialize
#endif
foreign import ccall "g_icon_to_string" g_icon_to_string ::
Ptr Icon ->
IO CString
iconToString ::
(B.CallStack.HasCallStack, MonadIO m, IsIcon a) =>
a
-> m (Maybe T.Text)
iconToString :: a -> m (Maybe Text)
iconToString a
icon = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr Icon
icon' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
CString
result <- Ptr Icon -> IO CString
g_icon_to_string Ptr Icon
icon'
Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data IconToStringMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsIcon a) => O.MethodInfo IconToStringMethodInfo a signature where
overloadedMethod = iconToString
#endif
foreign import ccall "g_icon_deserialize" g_icon_deserialize ::
Ptr GVariant ->
IO (Ptr Icon)
iconDeserialize ::
(B.CallStack.HasCallStack, MonadIO m) =>
GVariant
-> m Icon
iconDeserialize :: GVariant -> m Icon
iconDeserialize GVariant
value = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
Ptr GVariant
value' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
value
Ptr Icon
result <- Ptr GVariant -> IO (Ptr Icon)
g_icon_deserialize Ptr GVariant
value'
Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconDeserialize" Ptr Icon
result
Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Icon) Ptr Icon
result
GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
value
Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_icon_hash" g_icon_hash ::
Ptr () ->
IO Word32
iconHash ::
(B.CallStack.HasCallStack, MonadIO m) =>
Ptr ()
-> m Word32
iconHash :: Ptr () -> m Word32
iconHash Ptr ()
icon = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Word32
result <- Ptr () -> IO Word32
g_icon_hash Ptr ()
icon
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_icon_new_for_string" g_icon_new_for_string ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr Icon)
iconNewForString ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m Icon
iconNewForString :: Text -> m Icon
iconNewForString Text
str = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
CString
str' <- Text -> IO CString
textToCString Text
str
IO Icon -> IO () -> IO Icon
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Icon
result <- (Ptr (Ptr GError) -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Icon)) -> IO (Ptr Icon))
-> (Ptr (Ptr GError) -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Icon)
g_icon_new_for_string CString
str'
Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconNewForString" Ptr Icon
result
Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Icon) Ptr Icon
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
)
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Icon = IconSignalList
type IconSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif