{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- TODO

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

module GI.GIRepository.Structs.Typelib
    ( 

-- * Exported types
    Typelib(..)                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [free]("GI.GIRepository.Structs.Typelib#g:method:free"), [symbol]("GI.GIRepository.Structs.Typelib#g:method:symbol").
-- 
-- ==== Getters
-- [getNamespace]("GI.GIRepository.Structs.Typelib#g:method:getNamespace").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveTypelibMethod                    ,
#endif

-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    TypelibFreeMethodInfo                   ,
#endif
    typelibFree                             ,


-- ** getNamespace #method:getNamespace#

#if defined(ENABLE_OVERLOADING)
    TypelibGetNamespaceMethodInfo           ,
#endif
    typelibGetNamespace                     ,


-- ** symbol #method:symbol#

#if defined(ENABLE_OVERLOADING)
    TypelibSymbolMethodInfo                 ,
#endif
    typelibSymbol                           ,




    ) 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.GArray as B.GArray
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 GHC.Records as R


-- | Memory-managed wrapper type.
newtype Typelib = Typelib (SP.ManagedPtr Typelib)
    deriving (Typelib -> Typelib -> Bool
(Typelib -> Typelib -> Bool)
-> (Typelib -> Typelib -> Bool) -> Eq Typelib
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Typelib -> Typelib -> Bool
$c/= :: Typelib -> Typelib -> Bool
== :: Typelib -> Typelib -> Bool
$c== :: Typelib -> Typelib -> Bool
Eq)

instance SP.ManagedPtrNewtype Typelib where
    toManagedPtr :: Typelib -> ManagedPtr Typelib
toManagedPtr (Typelib ManagedPtr Typelib
p) = ManagedPtr Typelib
p

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr Typelib where
    boxedPtrCopy :: Typelib -> IO Typelib
boxedPtrCopy = Typelib -> IO Typelib
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: Typelib -> IO ()
boxedPtrFree = \Typelib
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


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

-- method Typelib::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "typelib"
--           , argType =
--               TInterface Name { namespace = "GIRepository" , name = "Typelib" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_typelib_free" g_typelib_free :: 
    Ptr Typelib ->                          -- typelib : TInterface (Name {namespace = "GIRepository", name = "Typelib"})
    IO ()

-- | /No description available in the introspection data./
typelibFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Typelib
    -> m ()
typelibFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Typelib -> m ()
typelibFree Typelib
typelib = 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 Typelib
typelib' <- Typelib -> IO (Ptr Typelib)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Typelib
typelib
    Ptr Typelib -> IO ()
g_typelib_free Ptr Typelib
typelib'
    Typelib -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Typelib
typelib
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TypelibFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TypelibFreeMethodInfo Typelib signature where
    overloadedMethod = typelibFree

instance O.OverloadedMethodInfo TypelibFreeMethodInfo Typelib where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GIRepository.Structs.Typelib.typelibFree",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-girepository-1.0.24/docs/GI-GIRepository-Structs-Typelib.html#v:typelibFree"
        }


#endif

-- method Typelib::get_namespace
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "typelib"
--           , argType =
--               TInterface Name { namespace = "GIRepository" , name = "Typelib" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_typelib_get_namespace" g_typelib_get_namespace :: 
    Ptr Typelib ->                          -- typelib : TInterface (Name {namespace = "GIRepository", name = "Typelib"})
    IO CString

-- | /No description available in the introspection data./
typelibGetNamespace ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Typelib
    -> m T.Text
typelibGetNamespace :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Typelib -> m Text
typelibGetNamespace Typelib
typelib = 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 Typelib
typelib' <- Typelib -> IO (Ptr Typelib)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Typelib
typelib
    CString
result <- Ptr Typelib -> IO CString
g_typelib_get_namespace Ptr Typelib
typelib'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"typelibGetNamespace" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    Typelib -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Typelib
typelib
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data TypelibGetNamespaceMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod TypelibGetNamespaceMethodInfo Typelib signature where
    overloadedMethod = typelibGetNamespace

instance O.OverloadedMethodInfo TypelibGetNamespaceMethodInfo Typelib where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GIRepository.Structs.Typelib.typelibGetNamespace",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-girepository-1.0.24/docs/GI-GIRepository-Structs-Typelib.html#v:typelibGetNamespace"
        }


#endif

-- method Typelib::symbol
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "typelib"
--           , argType =
--               TInterface Name { namespace = "GIRepository" , name = "Typelib" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "symbol_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "symbol"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_typelib_symbol" g_typelib_symbol :: 
    Ptr Typelib ->                          -- typelib : TInterface (Name {namespace = "GIRepository", name = "Typelib"})
    CString ->                              -- symbol_name : TBasicType TUTF8
    Ptr () ->                               -- symbol : TBasicType TPtr
    IO CInt

-- | /No description available in the introspection data./
typelibSymbol ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Typelib
    -> T.Text
    -> Ptr ()
    -> m Bool
typelibSymbol :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Typelib -> Text -> Ptr () -> m Bool
typelibSymbol Typelib
typelib Text
symbolName Ptr ()
symbol = 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 Typelib
typelib' <- Typelib -> IO (Ptr Typelib)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Typelib
typelib
    CString
symbolName' <- Text -> IO CString
textToCString Text
symbolName
    CInt
result <- Ptr Typelib -> CString -> Ptr () -> IO CInt
g_typelib_symbol Ptr Typelib
typelib' CString
symbolName' Ptr ()
symbol
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Typelib -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Typelib
typelib
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
symbolName'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TypelibSymbolMethodInfo
instance (signature ~ (T.Text -> Ptr () -> m Bool), MonadIO m) => O.OverloadedMethod TypelibSymbolMethodInfo Typelib signature where
    overloadedMethod = typelibSymbol

instance O.OverloadedMethodInfo TypelibSymbolMethodInfo Typelib where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GIRepository.Structs.Typelib.typelibSymbol",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-girepository-1.0.24/docs/GI-GIRepository-Structs-Typelib.html#v:typelibSymbol"
        }


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTypelibMethod (t :: Symbol) (o :: *) :: * where
    ResolveTypelibMethod "free" o = TypelibFreeMethodInfo
    ResolveTypelibMethod "symbol" o = TypelibSymbolMethodInfo
    ResolveTypelibMethod "getNamespace" o = TypelibGetNamespaceMethodInfo
    ResolveTypelibMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTypelibMethod t Typelib, O.OverloadedMethod info Typelib p, R.HasField t Typelib p) => R.HasField t Typelib p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveTypelibMethod t Typelib, O.OverloadedMethodInfo info Typelib) => OL.IsLabel t (O.MethodProxy info Typelib) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif