{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.ThemedIcon
(
ThemedIcon(..) ,
IsThemedIcon ,
toThemedIcon ,
#if defined(ENABLE_OVERLOADING)
ResolveThemedIconMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ThemedIconAppendNameMethodInfo ,
#endif
themedIconAppendName ,
#if defined(ENABLE_OVERLOADING)
ThemedIconGetNamesMethodInfo ,
#endif
themedIconGetNames ,
themedIconNew ,
themedIconNewFromNames ,
themedIconNewWithDefaultFallbacks ,
#if defined(ENABLE_OVERLOADING)
ThemedIconPrependNameMethodInfo ,
#endif
themedIconPrependName ,
#if defined(ENABLE_OVERLOADING)
ThemedIconNamePropertyInfo ,
#endif
constructThemedIconName ,
#if defined(ENABLE_OVERLOADING)
themedIconName ,
#endif
#if defined(ENABLE_OVERLOADING)
ThemedIconNamesPropertyInfo ,
#endif
constructThemedIconNames ,
getThemedIconNames ,
#if defined(ENABLE_OVERLOADING)
themedIconNames ,
#endif
#if defined(ENABLE_OVERLOADING)
ThemedIconUseDefaultFallbacksPropertyInfo,
#endif
constructThemedIconUseDefaultFallbacks ,
getThemedIconUseDefaultFallbacks ,
#if defined(ENABLE_OVERLOADING)
themedIconUseDefaultFallbacks ,
#endif
) 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
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
newtype ThemedIcon = ThemedIcon (SP.ManagedPtr ThemedIcon)
deriving (ThemedIcon -> ThemedIcon -> Bool
(ThemedIcon -> ThemedIcon -> Bool)
-> (ThemedIcon -> ThemedIcon -> Bool) -> Eq ThemedIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThemedIcon -> ThemedIcon -> Bool
$c/= :: ThemedIcon -> ThemedIcon -> Bool
== :: ThemedIcon -> ThemedIcon -> Bool
$c== :: ThemedIcon -> ThemedIcon -> Bool
Eq)
instance SP.ManagedPtrNewtype ThemedIcon where
toManagedPtr :: ThemedIcon -> ManagedPtr ThemedIcon
toManagedPtr (ThemedIcon ManagedPtr ThemedIcon
p) = ManagedPtr ThemedIcon
p
foreign import ccall "g_themed_icon_get_type"
c_g_themed_icon_get_type :: IO B.Types.GType
instance B.Types.TypedObject ThemedIcon where
glibType :: IO GType
glibType = IO GType
c_g_themed_icon_get_type
instance B.Types.GObject ThemedIcon
instance B.GValue.IsGValue ThemedIcon where
toGValue :: ThemedIcon -> IO GValue
toGValue ThemedIcon
o = do
GType
gtype <- IO GType
c_g_themed_icon_get_type
ThemedIcon -> (Ptr ThemedIcon -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ThemedIcon
o (GType
-> (GValue -> Ptr ThemedIcon -> IO ())
-> Ptr ThemedIcon
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ThemedIcon -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO ThemedIcon
fromGValue GValue
gv = do
Ptr ThemedIcon
ptr <- GValue -> IO (Ptr ThemedIcon)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ThemedIcon)
(ManagedPtr ThemedIcon -> ThemedIcon)
-> Ptr ThemedIcon -> IO ThemedIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon Ptr ThemedIcon
ptr
class (SP.GObject o, O.IsDescendantOf ThemedIcon o) => IsThemedIcon o
instance (SP.GObject o, O.IsDescendantOf ThemedIcon o) => IsThemedIcon o
instance O.HasParentTypes ThemedIcon
type instance O.ParentTypes ThemedIcon = '[GObject.Object.Object, Gio.Icon.Icon]
toThemedIcon :: (MonadIO m, IsThemedIcon o) => o -> m ThemedIcon
toThemedIcon :: o -> m ThemedIcon
toThemedIcon = IO ThemedIcon -> m ThemedIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemedIcon -> m ThemedIcon)
-> (o -> IO ThemedIcon) -> o -> m ThemedIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ThemedIcon -> ThemedIcon) -> o -> IO ThemedIcon
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon
#if defined(ENABLE_OVERLOADING)
type family ResolveThemedIconMethod (t :: Symbol) (o :: *) :: * where
ResolveThemedIconMethod "appendName" o = ThemedIconAppendNameMethodInfo
ResolveThemedIconMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveThemedIconMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveThemedIconMethod "equal" o = Gio.Icon.IconEqualMethodInfo
ResolveThemedIconMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveThemedIconMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveThemedIconMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveThemedIconMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveThemedIconMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveThemedIconMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveThemedIconMethod "prependName" o = ThemedIconPrependNameMethodInfo
ResolveThemedIconMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveThemedIconMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveThemedIconMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveThemedIconMethod "serialize" o = Gio.Icon.IconSerializeMethodInfo
ResolveThemedIconMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveThemedIconMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveThemedIconMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveThemedIconMethod "toString" o = Gio.Icon.IconToStringMethodInfo
ResolveThemedIconMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveThemedIconMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveThemedIconMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveThemedIconMethod "getNames" o = ThemedIconGetNamesMethodInfo
ResolveThemedIconMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveThemedIconMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveThemedIconMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveThemedIconMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveThemedIconMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveThemedIconMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveThemedIconMethod t ThemedIcon, O.MethodInfo info ThemedIcon p) => OL.IsLabel t (ThemedIcon -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
constructThemedIconName :: (IsThemedIcon o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructThemedIconName :: Text -> m (GValueConstruct o)
constructThemedIconName Text
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
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ThemedIconNamePropertyInfo
instance AttrInfo ThemedIconNamePropertyInfo where
type AttrAllowedOps ThemedIconNamePropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint ThemedIconNamePropertyInfo = IsThemedIcon
type AttrSetTypeConstraint ThemedIconNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ThemedIconNamePropertyInfo = (~) T.Text
type AttrTransferType ThemedIconNamePropertyInfo = T.Text
type AttrGetType ThemedIconNamePropertyInfo = ()
type AttrLabel ThemedIconNamePropertyInfo = "name"
type AttrOrigin ThemedIconNamePropertyInfo = ThemedIcon
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructThemedIconName
attrClear = undefined
#endif
getThemedIconNames :: (MonadIO m, IsThemedIcon o) => o -> m [T.Text]
getThemedIconNames :: o -> m [Text]
getThemedIconNames o
obj = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe [Text]) -> IO [Text]
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getThemedIconNames" (IO (Maybe [Text]) -> IO [Text]) -> IO (Maybe [Text]) -> IO [Text]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"names"
constructThemedIconNames :: (IsThemedIcon o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructThemedIconNames :: [Text] -> m (GValueConstruct o)
constructThemedIconNames [Text]
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
$ String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray String
"names" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
#if defined(ENABLE_OVERLOADING)
data ThemedIconNamesPropertyInfo
instance AttrInfo ThemedIconNamesPropertyInfo where
type AttrAllowedOps ThemedIconNamesPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ThemedIconNamesPropertyInfo = IsThemedIcon
type AttrSetTypeConstraint ThemedIconNamesPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint ThemedIconNamesPropertyInfo = (~) [T.Text]
type AttrTransferType ThemedIconNamesPropertyInfo = [T.Text]
type AttrGetType ThemedIconNamesPropertyInfo = [T.Text]
type AttrLabel ThemedIconNamesPropertyInfo = "names"
type AttrOrigin ThemedIconNamesPropertyInfo = ThemedIcon
attrGet = getThemedIconNames
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructThemedIconNames
attrClear = undefined
#endif
getThemedIconUseDefaultFallbacks :: (MonadIO m, IsThemedIcon o) => o -> m Bool
getThemedIconUseDefaultFallbacks :: o -> m Bool
getThemedIconUseDefaultFallbacks o
obj = 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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"use-default-fallbacks"
constructThemedIconUseDefaultFallbacks :: (IsThemedIcon o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructThemedIconUseDefaultFallbacks :: Bool -> m (GValueConstruct o)
constructThemedIconUseDefaultFallbacks Bool
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
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-default-fallbacks" Bool
val
#if defined(ENABLE_OVERLOADING)
data ThemedIconUseDefaultFallbacksPropertyInfo
instance AttrInfo ThemedIconUseDefaultFallbacksPropertyInfo where
type AttrAllowedOps ThemedIconUseDefaultFallbacksPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = IsThemedIcon
type AttrSetTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = (~) Bool
type AttrTransferTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = (~) Bool
type AttrTransferType ThemedIconUseDefaultFallbacksPropertyInfo = Bool
type AttrGetType ThemedIconUseDefaultFallbacksPropertyInfo = Bool
type AttrLabel ThemedIconUseDefaultFallbacksPropertyInfo = "use-default-fallbacks"
type AttrOrigin ThemedIconUseDefaultFallbacksPropertyInfo = ThemedIcon
attrGet = getThemedIconUseDefaultFallbacks
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructThemedIconUseDefaultFallbacks
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ThemedIcon
type instance O.AttributeList ThemedIcon = ThemedIconAttributeList
type ThemedIconAttributeList = ('[ '("name", ThemedIconNamePropertyInfo), '("names", ThemedIconNamesPropertyInfo), '("useDefaultFallbacks", ThemedIconUseDefaultFallbacksPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
themedIconName :: AttrLabelProxy "name"
themedIconName = AttrLabelProxy
themedIconNames :: AttrLabelProxy "names"
themedIconNames = AttrLabelProxy
themedIconUseDefaultFallbacks :: AttrLabelProxy "useDefaultFallbacks"
themedIconUseDefaultFallbacks = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ThemedIcon = ThemedIconSignalList
type ThemedIconSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_themed_icon_new" g_themed_icon_new ::
CString ->
IO (Ptr ThemedIcon)
themedIconNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m ThemedIcon
themedIconNew :: Text -> m ThemedIcon
themedIconNew Text
iconname = IO ThemedIcon -> m ThemedIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemedIcon -> m ThemedIcon) -> IO ThemedIcon -> m ThemedIcon
forall a b. (a -> b) -> a -> b
$ do
CString
iconname' <- Text -> IO CString
textToCString Text
iconname
Ptr ThemedIcon
result <- CString -> IO (Ptr ThemedIcon)
g_themed_icon_new CString
iconname'
Text -> Ptr ThemedIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconNew" Ptr ThemedIcon
result
ThemedIcon
result' <- ((ManagedPtr ThemedIcon -> ThemedIcon)
-> Ptr ThemedIcon -> IO ThemedIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon) Ptr ThemedIcon
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
ThemedIcon -> IO ThemedIcon
forall (m :: * -> *) a. Monad m => a -> m a
return ThemedIcon
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_themed_icon_new_from_names" g_themed_icon_new_from_names ::
Ptr CString ->
Int32 ->
IO (Ptr ThemedIcon)
themedIconNewFromNames ::
(B.CallStack.HasCallStack, MonadIO m) =>
[T.Text]
-> m ThemedIcon
themedIconNewFromNames :: [Text] -> m ThemedIcon
themedIconNewFromNames [Text]
iconnames = IO ThemedIcon -> m ThemedIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemedIcon -> m ThemedIcon) -> IO ThemedIcon -> m ThemedIcon
forall a b. (a -> b) -> a -> b
$ do
let len :: Int32
len = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Text]
iconnames
Ptr CString
iconnames' <- [Text] -> IO (Ptr CString)
packUTF8CArray [Text]
iconnames
Ptr ThemedIcon
result <- Ptr CString -> Int32 -> IO (Ptr ThemedIcon)
g_themed_icon_new_from_names Ptr CString
iconnames' Int32
len
Text -> Ptr ThemedIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconNewFromNames" Ptr ThemedIcon
result
ThemedIcon
result' <- ((ManagedPtr ThemedIcon -> ThemedIcon)
-> Ptr ThemedIcon -> IO ThemedIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon) Ptr ThemedIcon
result
(Int32 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Int32
len) CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconnames'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconnames'
ThemedIcon -> IO ThemedIcon
forall (m :: * -> *) a. Monad m => a -> m a
return ThemedIcon
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_themed_icon_new_with_default_fallbacks" g_themed_icon_new_with_default_fallbacks ::
CString ->
IO (Ptr ThemedIcon)
themedIconNewWithDefaultFallbacks ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m ThemedIcon
themedIconNewWithDefaultFallbacks :: Text -> m ThemedIcon
themedIconNewWithDefaultFallbacks Text
iconname = IO ThemedIcon -> m ThemedIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemedIcon -> m ThemedIcon) -> IO ThemedIcon -> m ThemedIcon
forall a b. (a -> b) -> a -> b
$ do
CString
iconname' <- Text -> IO CString
textToCString Text
iconname
Ptr ThemedIcon
result <- CString -> IO (Ptr ThemedIcon)
g_themed_icon_new_with_default_fallbacks CString
iconname'
Text -> Ptr ThemedIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconNewWithDefaultFallbacks" Ptr ThemedIcon
result
ThemedIcon
result' <- ((ManagedPtr ThemedIcon -> ThemedIcon)
-> Ptr ThemedIcon -> IO ThemedIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon) Ptr ThemedIcon
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
ThemedIcon -> IO ThemedIcon
forall (m :: * -> *) a. Monad m => a -> m a
return ThemedIcon
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_themed_icon_append_name" g_themed_icon_append_name ::
Ptr ThemedIcon ->
CString ->
IO ()
themedIconAppendName ::
(B.CallStack.HasCallStack, MonadIO m, IsThemedIcon a) =>
a
-> T.Text
-> m ()
themedIconAppendName :: a -> Text -> m ()
themedIconAppendName a
icon Text
iconname = 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 ThemedIcon
icon' <- a -> IO (Ptr ThemedIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
CString
iconname' <- Text -> IO CString
textToCString Text
iconname
Ptr ThemedIcon -> CString -> IO ()
g_themed_icon_append_name Ptr ThemedIcon
icon' CString
iconname'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ThemedIconAppendNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsThemedIcon a) => O.MethodInfo ThemedIconAppendNameMethodInfo a signature where
overloadedMethod = themedIconAppendName
#endif
foreign import ccall "g_themed_icon_get_names" g_themed_icon_get_names ::
Ptr ThemedIcon ->
IO (Ptr CString)
themedIconGetNames ::
(B.CallStack.HasCallStack, MonadIO m, IsThemedIcon a) =>
a
-> m [T.Text]
themedIconGetNames :: a -> m [Text]
themedIconGetNames a
icon = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
Ptr ThemedIcon
icon' <- a -> IO (Ptr ThemedIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
Ptr CString
result <- Ptr ThemedIcon -> IO (Ptr CString)
g_themed_icon_get_names Ptr ThemedIcon
icon'
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconGetNames" Ptr CString
result
[Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
[Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data ThemedIconGetNamesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsThemedIcon a) => O.MethodInfo ThemedIconGetNamesMethodInfo a signature where
overloadedMethod = themedIconGetNames
#endif
foreign import ccall "g_themed_icon_prepend_name" g_themed_icon_prepend_name ::
Ptr ThemedIcon ->
CString ->
IO ()
themedIconPrependName ::
(B.CallStack.HasCallStack, MonadIO m, IsThemedIcon a) =>
a
-> T.Text
-> m ()
themedIconPrependName :: a -> Text -> m ()
themedIconPrependName a
icon Text
iconname = 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 ThemedIcon
icon' <- a -> IO (Ptr ThemedIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
CString
iconname' <- Text -> IO CString
textToCString Text
iconname
Ptr ThemedIcon -> CString -> IO ()
g_themed_icon_prepend_name Ptr ThemedIcon
icon' CString
iconname'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ThemedIconPrependNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsThemedIcon a) => O.MethodInfo ThemedIconPrependNameMethodInfo a signature where
overloadedMethod = themedIconPrependName
#endif