{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.FileIcon.FileIcon' specifies an icon by pointing to an image file
-- to be used as icon.

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

module GI.Gio.Objects.FileIcon
    ( 

-- * Exported types
    FileIcon(..)                            ,
    IsFileIcon                              ,
    toFileIcon                              ,
    noFileIcon                              ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveFileIconMethod                   ,
#endif


-- ** getFile #method:getFile#

#if defined(ENABLE_OVERLOADING)
    FileIconGetFileMethodInfo               ,
#endif
    fileIconGetFile                         ,


-- ** new #method:new#

    fileIconNew                             ,




 -- * Properties
-- ** file #attr:file#
-- | The file containing the icon.

#if defined(ENABLE_OVERLOADING)
    FileIconFilePropertyInfo                ,
#endif
    constructFileIconFile                   ,
#if defined(ENABLE_OVERLOADING)
    fileIconFile                            ,
#endif
    getFileIconFile                         ,




    ) 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.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 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.File as Gio.File
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Interfaces.LoadableIcon as Gio.LoadableIcon

-- | Memory-managed wrapper type.
newtype FileIcon = FileIcon (ManagedPtr FileIcon)
    deriving (FileIcon -> FileIcon -> Bool
(FileIcon -> FileIcon -> Bool)
-> (FileIcon -> FileIcon -> Bool) -> Eq FileIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileIcon -> FileIcon -> Bool
$c/= :: FileIcon -> FileIcon -> Bool
== :: FileIcon -> FileIcon -> Bool
$c== :: FileIcon -> FileIcon -> Bool
Eq)
foreign import ccall "g_file_icon_get_type"
    c_g_file_icon_get_type :: IO GType

instance GObject FileIcon where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_file_icon_get_type
    

-- | Convert 'FileIcon' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue FileIcon where
    toGValue :: FileIcon -> IO GValue
toGValue o :: FileIcon
o = do
        GType
gtype <- IO GType
c_g_file_icon_get_type
        FileIcon -> (Ptr FileIcon -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileIcon
o (GType
-> (GValue -> Ptr FileIcon -> IO ()) -> Ptr FileIcon -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr FileIcon -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO FileIcon
fromGValue gv :: GValue
gv = do
        Ptr FileIcon
ptr <- GValue -> IO (Ptr FileIcon)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr FileIcon)
        (ManagedPtr FileIcon -> FileIcon) -> Ptr FileIcon -> IO FileIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FileIcon -> FileIcon
FileIcon Ptr FileIcon
ptr
        
    

-- | Type class for types which can be safely cast to `FileIcon`, for instance with `toFileIcon`.
class (GObject o, O.IsDescendantOf FileIcon o) => IsFileIcon o
instance (GObject o, O.IsDescendantOf FileIcon o) => IsFileIcon o

instance O.HasParentTypes FileIcon
type instance O.ParentTypes FileIcon = '[GObject.Object.Object, Gio.Icon.Icon, Gio.LoadableIcon.LoadableIcon]

-- | Cast to `FileIcon`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toFileIcon :: (MonadIO m, IsFileIcon o) => o -> m FileIcon
toFileIcon :: o -> m FileIcon
toFileIcon = IO FileIcon -> m FileIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileIcon -> m FileIcon)
-> (o -> IO FileIcon) -> o -> m FileIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FileIcon -> FileIcon) -> o -> IO FileIcon
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr FileIcon -> FileIcon
FileIcon

-- | A convenience alias for `Nothing` :: `Maybe` `FileIcon`.
noFileIcon :: Maybe FileIcon
noFileIcon :: Maybe FileIcon
noFileIcon = Maybe FileIcon
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveFileIconMethod (t :: Symbol) (o :: *) :: * where
    ResolveFileIconMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveFileIconMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveFileIconMethod "equal" o = Gio.Icon.IconEqualMethodInfo
    ResolveFileIconMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveFileIconMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveFileIconMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveFileIconMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveFileIconMethod "load" o = Gio.LoadableIcon.LoadableIconLoadMethodInfo
    ResolveFileIconMethod "loadAsync" o = Gio.LoadableIcon.LoadableIconLoadAsyncMethodInfo
    ResolveFileIconMethod "loadFinish" o = Gio.LoadableIcon.LoadableIconLoadFinishMethodInfo
    ResolveFileIconMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveFileIconMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveFileIconMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveFileIconMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveFileIconMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveFileIconMethod "serialize" o = Gio.Icon.IconSerializeMethodInfo
    ResolveFileIconMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveFileIconMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveFileIconMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveFileIconMethod "toString" o = Gio.Icon.IconToStringMethodInfo
    ResolveFileIconMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveFileIconMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveFileIconMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveFileIconMethod "getFile" o = FileIconGetFileMethodInfo
    ResolveFileIconMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveFileIconMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveFileIconMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveFileIconMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveFileIconMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveFileIconMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFileIconMethod t FileIcon, O.MethodInfo info FileIcon p) => OL.IsLabel t (FileIcon -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- VVV Prop "file"
   -- Type: TInterface (Name {namespace = "Gio", name = "File"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' fileIcon #file
-- @
getFileIconFile :: (MonadIO m, IsFileIcon o) => o -> m Gio.File.File
getFileIconFile :: o -> m File
getFileIconFile obj :: o
obj = IO File -> m File
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe File) -> IO File
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getFileIconFile" (IO (Maybe File) -> IO File) -> IO (Maybe File) -> IO File
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr File -> File) -> IO (Maybe File)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "file" ManagedPtr File -> File
Gio.File.File

-- | Construct a `GValueConstruct` with valid value for the “@file@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFileIconFile :: (IsFileIcon o, Gio.File.IsFile a) => a -> IO (GValueConstruct o)
constructFileIconFile :: a -> IO (GValueConstruct o)
constructFileIconFile val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "file" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

#if defined(ENABLE_OVERLOADING)
data FileIconFilePropertyInfo
instance AttrInfo FileIconFilePropertyInfo where
    type AttrAllowedOps FileIconFilePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint FileIconFilePropertyInfo = IsFileIcon
    type AttrSetTypeConstraint FileIconFilePropertyInfo = Gio.File.IsFile
    type AttrTransferTypeConstraint FileIconFilePropertyInfo = Gio.File.IsFile
    type AttrTransferType FileIconFilePropertyInfo = Gio.File.File
    type AttrGetType FileIconFilePropertyInfo = Gio.File.File
    type AttrLabel FileIconFilePropertyInfo = "file"
    type AttrOrigin FileIconFilePropertyInfo = FileIcon
    attrGet = getFileIconFile
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.File.File v
    attrConstruct = constructFileIconFile
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileIcon
type instance O.AttributeList FileIcon = FileIconAttributeList
type FileIconAttributeList = ('[ '("file", FileIconFilePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
fileIconFile :: AttrLabelProxy "file"
fileIconFile = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FileIcon = FileIconSignalList
type FileIconSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method FileIcon::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFile." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "FileIcon" })
-- throws : False
-- Skip return : False

foreign import ccall "g_file_icon_new" g_file_icon_new :: 
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    IO (Ptr FileIcon)

-- | Creates a new icon for a file.
fileIconNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a) =>
    a
    -- ^ /@file@/: a t'GI.Gio.Interfaces.File.File'.
    -> m FileIcon
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.Icon.Icon' for the given
    --   /@file@/, or 'P.Nothing' on error.
fileIconNew :: a -> m FileIcon
fileIconNew file :: a
file = IO FileIcon -> m FileIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileIcon -> m FileIcon) -> IO FileIcon -> m FileIcon
forall a b. (a -> b) -> a -> b
$ do
    Ptr File
file' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
file
    Ptr FileIcon
result <- Ptr File -> IO (Ptr FileIcon)
g_file_icon_new Ptr File
file'
    Text -> Ptr FileIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileIconNew" Ptr FileIcon
result
    FileIcon
result' <- ((ManagedPtr FileIcon -> FileIcon) -> Ptr FileIcon -> IO FileIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr FileIcon -> FileIcon
FileIcon) Ptr FileIcon
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
file
    FileIcon -> IO FileIcon
forall (m :: * -> *) a. Monad m => a -> m a
return FileIcon
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FileIcon::get_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "File" })
-- throws : False
-- Skip return : False

foreign import ccall "g_file_icon_get_file" g_file_icon_get_file :: 
    Ptr FileIcon ->                         -- icon : TInterface (Name {namespace = "Gio", name = "FileIcon"})
    IO (Ptr Gio.File.File)

-- | Gets the t'GI.Gio.Interfaces.File.File' associated with the given /@icon@/.
fileIconGetFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileIcon a) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon'.
    -> m Gio.File.File
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.File.File', or 'P.Nothing'.
fileIconGetFile :: a -> m File
fileIconGetFile icon :: a
icon = IO File -> m File
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileIcon
icon' <- a -> IO (Ptr FileIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr File
result <- Ptr FileIcon -> IO (Ptr File)
g_file_icon_get_file Ptr FileIcon
icon'
    Text -> Ptr File -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileIconGetFile" Ptr File
result
    File
result' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    File -> IO File
forall (m :: * -> *) a. Monad m => a -> m a
return File
result'

#if defined(ENABLE_OVERLOADING)
data FileIconGetFileMethodInfo
instance (signature ~ (m Gio.File.File), MonadIO m, IsFileIcon a) => O.MethodInfo FileIconGetFileMethodInfo a signature where
    overloadedMethod = fileIconGetFile

#endif