{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gio.Objects.ThemedIcon
    ( 

-- * Exported types
    ThemedIcon(..)                          ,
    ThemedIconK                             ,
    toThemedIcon                            ,
    noThemedIcon                            ,


 -- * Methods
-- ** themedIconAppendName
    themedIconAppendName                    ,


-- ** themedIconGetNames
    themedIconGetNames                      ,


-- ** themedIconNew
    themedIconNew                           ,


-- ** themedIconNewFromNames
    themedIconNewFromNames                  ,


-- ** themedIconNewWithDefaultFallbacks
    themedIconNewWithDefaultFallbacks       ,


-- ** themedIconPrependName
    themedIconPrependName                   ,




 -- * Properties
-- ** Name
    ThemedIconNamePropertyInfo              ,
    constructThemedIconName                 ,


-- ** Names
    ThemedIconNamesPropertyInfo             ,
    constructThemedIconNames                ,
    getThemedIconNames                      ,


-- ** UseDefaultFallbacks
    ThemedIconUseDefaultFallbacksPropertyInfo,
    constructThemedIconUseDefaultFallbacks  ,
    getThemedIconUseDefaultFallbacks        ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gio.Types
import GI.Gio.Callbacks
import qualified GI.GObject as GObject

newtype ThemedIcon = ThemedIcon (ForeignPtr ThemedIcon)
foreign import ccall "g_themed_icon_get_type"
    c_g_themed_icon_get_type :: IO GType

type instance ParentTypes ThemedIcon = ThemedIconParentTypes
type ThemedIconParentTypes = '[GObject.Object, Icon]

instance GObject ThemedIcon where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_g_themed_icon_get_type
    

class GObject o => ThemedIconK o
instance (GObject o, IsDescendantOf ThemedIcon o) => ThemedIconK o

toThemedIcon :: ThemedIconK o => o -> IO ThemedIcon
toThemedIcon = unsafeCastTo ThemedIcon

noThemedIcon :: Maybe ThemedIcon
noThemedIcon = Nothing

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyWritable,PropertyConstructOnly]

constructThemedIconName :: T.Text -> IO ([Char], GValue)
constructThemedIconName val = constructObjectPropertyString "name" val

data ThemedIconNamePropertyInfo
instance AttrInfo ThemedIconNamePropertyInfo where
    type AttrAllowedOps ThemedIconNamePropertyInfo = '[ 'AttrConstruct]
    type AttrSetTypeConstraint ThemedIconNamePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint ThemedIconNamePropertyInfo = ThemedIconK
    type AttrGetType ThemedIconNamePropertyInfo = ()
    type AttrLabel ThemedIconNamePropertyInfo = "ThemedIcon::name"
    attrGet _ = undefined
    attrSet _ = undefined
    attrConstruct _ = constructThemedIconName

-- VVV Prop "names"
   -- Type: TCArray True (-1) (-1) (TBasicType TUTF8)
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getThemedIconNames :: (MonadIO m, ThemedIconK o) => o -> m [T.Text]
getThemedIconNames obj = liftIO $ getObjectPropertyStringArray obj "names"

constructThemedIconNames :: [T.Text] -> IO ([Char], GValue)
constructThemedIconNames val = constructObjectPropertyStringArray "names" val

data ThemedIconNamesPropertyInfo
instance AttrInfo ThemedIconNamesPropertyInfo where
    type AttrAllowedOps ThemedIconNamesPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ThemedIconNamesPropertyInfo = (~) [T.Text]
    type AttrBaseTypeConstraint ThemedIconNamesPropertyInfo = ThemedIconK
    type AttrGetType ThemedIconNamesPropertyInfo = [T.Text]
    type AttrLabel ThemedIconNamesPropertyInfo = "ThemedIcon::names"
    attrGet _ = getThemedIconNames
    attrSet _ = undefined
    attrConstruct _ = constructThemedIconNames

-- VVV Prop "use-default-fallbacks"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getThemedIconUseDefaultFallbacks :: (MonadIO m, ThemedIconK o) => o -> m Bool
getThemedIconUseDefaultFallbacks obj = liftIO $ getObjectPropertyBool obj "use-default-fallbacks"

constructThemedIconUseDefaultFallbacks :: Bool -> IO ([Char], GValue)
constructThemedIconUseDefaultFallbacks val = constructObjectPropertyBool "use-default-fallbacks" val

data ThemedIconUseDefaultFallbacksPropertyInfo
instance AttrInfo ThemedIconUseDefaultFallbacksPropertyInfo where
    type AttrAllowedOps ThemedIconUseDefaultFallbacksPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = ThemedIconK
    type AttrGetType ThemedIconUseDefaultFallbacksPropertyInfo = Bool
    type AttrLabel ThemedIconUseDefaultFallbacksPropertyInfo = "ThemedIcon::use-default-fallbacks"
    attrGet _ = getThemedIconUseDefaultFallbacks
    attrSet _ = undefined
    attrConstruct _ = constructThemedIconUseDefaultFallbacks

type instance AttributeList ThemedIcon = ThemedIconAttributeList
type ThemedIconAttributeList = ('[ '("name", ThemedIconNamePropertyInfo), '("names", ThemedIconNamesPropertyInfo), '("use-default-fallbacks", ThemedIconUseDefaultFallbacksPropertyInfo)] :: [(Symbol, *)])

type instance SignalList ThemedIcon = ThemedIconSignalList
type ThemedIconSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method ThemedIcon::new
-- method type : Constructor
-- Args : [Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "ThemedIcon"
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_new" g_themed_icon_new :: 
    CString ->                              -- iconname : TBasicType TUTF8
    IO (Ptr ThemedIcon)


themedIconNew ::
    (MonadIO m) =>
    T.Text ->                               -- iconname
    m ThemedIcon
themedIconNew iconname = liftIO $ do
    iconname' <- textToCString iconname
    result <- g_themed_icon_new iconname'
    checkUnexpectedReturnNULL "g_themed_icon_new" result
    result' <- (wrapObject ThemedIcon) result
    freeMem iconname'
    return result'

-- method ThemedIcon::new_from_names
-- method type : Constructor
-- Args : [Arg {argName = "iconnames", argType = TCArray False (-1) 1 (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "iconnames", argType = TCArray False (-1) 1 (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "ThemedIcon"
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_new_from_names" g_themed_icon_new_from_names :: 
    Ptr CString ->                          -- iconnames : TCArray False (-1) 1 (TBasicType TUTF8)
    Int32 ->                                -- len : TBasicType TInt32
    IO (Ptr ThemedIcon)


themedIconNewFromNames ::
    (MonadIO m) =>
    [T.Text] ->                             -- iconnames
    m ThemedIcon
themedIconNewFromNames iconnames = liftIO $ do
    let len = fromIntegral $ length iconnames
    iconnames' <- packUTF8CArray iconnames
    result <- g_themed_icon_new_from_names iconnames' len
    checkUnexpectedReturnNULL "g_themed_icon_new_from_names" result
    result' <- (wrapObject ThemedIcon) result
    (mapCArrayWithLength len) freeMem iconnames'
    freeMem iconnames'
    return result'

-- method ThemedIcon::new_with_default_fallbacks
-- method type : Constructor
-- Args : [Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "ThemedIcon"
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_new_with_default_fallbacks" g_themed_icon_new_with_default_fallbacks :: 
    CString ->                              -- iconname : TBasicType TUTF8
    IO (Ptr ThemedIcon)


themedIconNewWithDefaultFallbacks ::
    (MonadIO m) =>
    T.Text ->                               -- iconname
    m ThemedIcon
themedIconNewWithDefaultFallbacks iconname = liftIO $ do
    iconname' <- textToCString iconname
    result <- g_themed_icon_new_with_default_fallbacks iconname'
    checkUnexpectedReturnNULL "g_themed_icon_new_with_default_fallbacks" result
    result' <- (wrapObject ThemedIcon) result
    freeMem iconname'
    return result'

-- method ThemedIcon::append_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "ThemedIcon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "ThemedIcon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_append_name" g_themed_icon_append_name :: 
    Ptr ThemedIcon ->                       -- _obj : TInterface "Gio" "ThemedIcon"
    CString ->                              -- iconname : TBasicType TUTF8
    IO ()


themedIconAppendName ::
    (MonadIO m, ThemedIconK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- iconname
    m ()
themedIconAppendName _obj iconname = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    iconname' <- textToCString iconname
    g_themed_icon_append_name _obj' iconname'
    touchManagedPtr _obj
    freeMem iconname'
    return ()

-- method ThemedIcon::get_names
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "ThemedIcon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "ThemedIcon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_get_names" g_themed_icon_get_names :: 
    Ptr ThemedIcon ->                       -- _obj : TInterface "Gio" "ThemedIcon"
    IO (Ptr CString)


themedIconGetNames ::
    (MonadIO m, ThemedIconK a) =>
    a ->                                    -- _obj
    m [T.Text]
themedIconGetNames _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_themed_icon_get_names _obj'
    checkUnexpectedReturnNULL "g_themed_icon_get_names" result
    result' <- unpackZeroTerminatedUTF8CArray result
    touchManagedPtr _obj
    return result'

-- method ThemedIcon::prepend_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "ThemedIcon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "ThemedIcon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iconname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_prepend_name" g_themed_icon_prepend_name :: 
    Ptr ThemedIcon ->                       -- _obj : TInterface "Gio" "ThemedIcon"
    CString ->                              -- iconname : TBasicType TUTF8
    IO ()


themedIconPrependName ::
    (MonadIO m, ThemedIconK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- iconname
    m ()
themedIconPrependName _obj iconname = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    iconname' <- textToCString iconname
    g_themed_icon_prepend_name _obj' iconname'
    touchManagedPtr _obj
    freeMem iconname'
    return ()