{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a git proxy options.

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

module GI.Ggit.Objects.ProxyOptions
    ( 

-- * Exported types
    ProxyOptions(..)                        ,
    IsProxyOptions                          ,
    toProxyOptions                          ,
    noProxyOptions                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveProxyOptionsMethod               ,
#endif


-- ** new #method:new#

    proxyOptionsNew                         ,




    ) 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

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

instance GObject ProxyOptions where
    gobjectType :: IO GType
gobjectType = IO GType
c_ggit_proxy_options_get_type
    

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

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

instance O.HasParentTypes ProxyOptions
type instance O.ParentTypes ProxyOptions = '[GObject.Object.Object]

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

-- | A convenience alias for `Nothing` :: `Maybe` `ProxyOptions`.
noProxyOptions :: Maybe ProxyOptions
noProxyOptions :: Maybe ProxyOptions
noProxyOptions = Maybe ProxyOptions
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveProxyOptionsMethod (t :: Symbol) (o :: *) :: * where
    ResolveProxyOptionsMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveProxyOptionsMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveProxyOptionsMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveProxyOptionsMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveProxyOptionsMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveProxyOptionsMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveProxyOptionsMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveProxyOptionsMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveProxyOptionsMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveProxyOptionsMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveProxyOptionsMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveProxyOptionsMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveProxyOptionsMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveProxyOptionsMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveProxyOptionsMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveProxyOptionsMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveProxyOptionsMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveProxyOptionsMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveProxyOptionsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveProxyOptionsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveProxyOptionsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveProxyOptionsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveProxyOptionsMethod l o = O.MethodResolutionFailed l o

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ProxyOptions
type instance O.AttributeList ProxyOptions = ProxyOptionsAttributeList
type ProxyOptionsAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method ProxyOptions::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Ggit" , name = "ProxyOptions" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_proxy_options_new" ggit_proxy_options_new :: 
    IO (Ptr ProxyOptions)

-- | Create a new proxy options object.
proxyOptionsNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe ProxyOptions)
    -- ^ __Returns:__ a t'GI.Ggit.Objects.ProxyOptions.ProxyOptions'.
proxyOptionsNew :: m (Maybe ProxyOptions)
proxyOptionsNew  = IO (Maybe ProxyOptions) -> m (Maybe ProxyOptions)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ProxyOptions) -> m (Maybe ProxyOptions))
-> IO (Maybe ProxyOptions) -> m (Maybe ProxyOptions)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ProxyOptions
result <- IO (Ptr ProxyOptions)
ggit_proxy_options_new
    Maybe ProxyOptions
maybeResult <- Ptr ProxyOptions
-> (Ptr ProxyOptions -> IO ProxyOptions) -> IO (Maybe ProxyOptions)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ProxyOptions
result ((Ptr ProxyOptions -> IO ProxyOptions) -> IO (Maybe ProxyOptions))
-> (Ptr ProxyOptions -> IO ProxyOptions) -> IO (Maybe ProxyOptions)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr ProxyOptions
result' -> do
        ProxyOptions
result'' <- ((ManagedPtr ProxyOptions -> ProxyOptions)
-> Ptr ProxyOptions -> IO ProxyOptions
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ProxyOptions -> ProxyOptions
ProxyOptions) Ptr ProxyOptions
result'
        ProxyOptions -> IO ProxyOptions
forall (m :: * -> *) a. Monad m => a -> m a
return ProxyOptions
result''
    Maybe ProxyOptions -> IO (Maybe ProxyOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ProxyOptions
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif