{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GRelation@ is a table of data which can be indexed on any number
-- of fields, rather like simple database tables. A @GRelation@ contains
-- a number of records, called tuples. Each record contains a number of
-- fields. Records are not ordered, so it is not possible to find the
-- record at a particular index.
-- 
-- Note that @GRelation@ tables are currently limited to 2 fields.
-- 
-- To create a @GRelation@, use [func/@gLib@/.Relation.new].
-- 
-- To specify which fields should be indexed, use t'GI.GLib.Structs.Relation.Relation'.@/index/@().
-- Note that this must be called before any tuples are added to the
-- @GRelation@.
-- 
-- To add records to a @GRelation@ use t'GI.GLib.Structs.Relation.Relation'.@/insert/@().
-- 
-- To determine if a given record appears in a @GRelation@, use
-- t'GI.GLib.Structs.Relation.Relation'.@/exists/@(). Note that fields are compared directly, so
-- pointers must point to the exact same position (i.e. different
-- copies of the same string will not match.)
-- 
-- To count the number of records which have a particular value in a
-- given field, use 'GI.GLib.Structs.Relation.relationCount'.
-- 
-- To get all the records which have a particular value in a given
-- field, use t'GI.GLib.Structs.Relation.Relation'.@/select/@(). To access fields of the resulting
-- records, use 'GI.GLib.Structs.Tuples.tuplesIndex'. To free the resulting records use
-- 'GI.GLib.Structs.Tuples.tuplesDestroy'.
-- 
-- To delete all records which have a particular value in a given
-- field, use 'GI.GLib.Structs.Relation.relationDelete'.
-- 
-- To destroy the @GRelation@, use 'GI.GLib.Structs.Relation.relationDestroy'.
-- 
-- To help debug @GRelation@ objects, use 'GI.GLib.Structs.Relation.relationPrint'.
-- 
-- @GRelation@ has been marked as deprecated, since this API has never
-- been fully implemented, is not very actively maintained and rarely
-- used.

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

module GI.GLib.Structs.Relation
    ( 

-- * Exported types
    Relation(..)                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [count]("GI.GLib.Structs.Relation#g:method:count"), [delete]("GI.GLib.Structs.Relation#g:method:delete"), [destroy]("GI.GLib.Structs.Relation#g:method:destroy"), [print]("GI.GLib.Structs.Relation#g:method:print").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveRelationMethod                   ,
#endif

-- ** count #method:count#

#if defined(ENABLE_OVERLOADING)
    RelationCountMethodInfo                 ,
#endif
    relationCount                           ,


-- ** delete #method:delete#

#if defined(ENABLE_OVERLOADING)
    RelationDeleteMethodInfo                ,
#endif
    relationDelete                          ,


-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    RelationDestroyMethodInfo               ,
#endif
    relationDestroy                         ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    RelationPrintMethodInfo                 ,
#endif
    relationPrint                           ,




    ) 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.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)

#else

#endif

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

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

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


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Relation
type instance O.AttributeList Relation = RelationAttributeList
type RelationAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

-- method Relation::count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Relation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRelation." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value to compare with."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "field"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the field of each record to match."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_relation_count" g_relation_count :: 
    Ptr Relation ->                         -- relation : TInterface (Name {namespace = "GLib", name = "Relation"})
    Ptr () ->                               -- key : TBasicType TPtr
    Int32 ->                                -- field : TBasicType TInt
    IO Int32

{-# DEPRECATED relationCount ["(Since version 2.26)","Rarely used API"] #-}
-- | Returns the number of tuples in a t'GI.GLib.Structs.Relation.Relation' that have the given
-- value in the given field.
relationCount ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Relation
    -- ^ /@relation@/: a t'GI.GLib.Structs.Relation.Relation'.
    -> Ptr ()
    -- ^ /@key@/: the value to compare with.
    -> Int32
    -- ^ /@field@/: the field of each record to match.
    -> m Int32
    -- ^ __Returns:__ the number of matches.
relationCount :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Relation -> Ptr () -> Int32 -> m Int32
relationCount Relation
relation Ptr ()
key Int32
field = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Relation
relation' <- Relation -> IO (Ptr Relation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Relation
relation
    Int32
result <- Ptr Relation -> Ptr () -> Int32 -> IO Int32
g_relation_count Ptr Relation
relation' Ptr ()
key Int32
field
    Relation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Relation
relation
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data RelationCountMethodInfo
instance (signature ~ (Ptr () -> Int32 -> m Int32), MonadIO m) => O.OverloadedMethod RelationCountMethodInfo Relation signature where
    overloadedMethod = relationCount

instance O.OverloadedMethodInfo RelationCountMethodInfo Relation where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Relation.relationCount",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Relation.html#v:relationCount"
        })


#endif

-- method Relation::delete
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Relation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRelation." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value to compare with."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "field"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the field of each record to match."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_relation_delete" g_relation_delete :: 
    Ptr Relation ->                         -- relation : TInterface (Name {namespace = "GLib", name = "Relation"})
    Ptr () ->                               -- key : TBasicType TPtr
    Int32 ->                                -- field : TBasicType TInt
    IO Int32

{-# DEPRECATED relationDelete ["(Since version 2.26)","Rarely used API"] #-}
-- | Deletes any records from a t'GI.GLib.Structs.Relation.Relation' that have the given key value
-- in the given field.
relationDelete ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Relation
    -- ^ /@relation@/: a t'GI.GLib.Structs.Relation.Relation'.
    -> Ptr ()
    -- ^ /@key@/: the value to compare with.
    -> Int32
    -- ^ /@field@/: the field of each record to match.
    -> m Int32
    -- ^ __Returns:__ the number of records deleted.
relationDelete :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Relation -> Ptr () -> Int32 -> m Int32
relationDelete Relation
relation Ptr ()
key Int32
field = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Relation
relation' <- Relation -> IO (Ptr Relation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Relation
relation
    Int32
result <- Ptr Relation -> Ptr () -> Int32 -> IO Int32
g_relation_delete Ptr Relation
relation' Ptr ()
key Int32
field
    Relation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Relation
relation
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data RelationDeleteMethodInfo
instance (signature ~ (Ptr () -> Int32 -> m Int32), MonadIO m) => O.OverloadedMethod RelationDeleteMethodInfo Relation signature where
    overloadedMethod = relationDelete

instance O.OverloadedMethodInfo RelationDeleteMethodInfo Relation where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Relation.relationDelete",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Relation.html#v:relationDelete"
        })


#endif

-- method Relation::destroy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Relation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRelation." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_relation_destroy" g_relation_destroy :: 
    Ptr Relation ->                         -- relation : TInterface (Name {namespace = "GLib", name = "Relation"})
    IO ()

{-# DEPRECATED relationDestroy ["(Since version 2.26)","Rarely used API"] #-}
-- | Destroys the t'GI.GLib.Structs.Relation.Relation', freeing all memory allocated. However, it
-- does not free memory allocated for the tuple data, so you should
-- free that first if appropriate.
relationDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Relation
    -- ^ /@relation@/: a t'GI.GLib.Structs.Relation.Relation'.
    -> m ()
relationDestroy :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Relation -> m ()
relationDestroy Relation
relation = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Relation
relation' <- Relation -> IO (Ptr Relation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Relation
relation
    Ptr Relation -> IO ()
g_relation_destroy Ptr Relation
relation'
    Relation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Relation
relation
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RelationDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RelationDestroyMethodInfo Relation signature where
    overloadedMethod = relationDestroy

instance O.OverloadedMethodInfo RelationDestroyMethodInfo Relation where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Relation.relationDestroy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Relation.html#v:relationDestroy"
        })


#endif

-- method Relation::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Relation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRelation." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_relation_print" g_relation_print :: 
    Ptr Relation ->                         -- relation : TInterface (Name {namespace = "GLib", name = "Relation"})
    IO ()

{-# DEPRECATED relationPrint ["(Since version 2.26)","Rarely used API"] #-}
-- | Outputs information about all records in a t'GI.GLib.Structs.Relation.Relation', as well as
-- the indexes. It is for debugging.
relationPrint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Relation
    -- ^ /@relation@/: a t'GI.GLib.Structs.Relation.Relation'.
    -> m ()
relationPrint :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Relation -> m ()
relationPrint Relation
relation = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Relation
relation' <- Relation -> IO (Ptr Relation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Relation
relation
    Ptr Relation -> IO ()
g_relation_print Ptr Relation
relation'
    Relation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Relation
relation
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RelationPrintMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RelationPrintMethodInfo Relation signature where
    overloadedMethod = relationPrint

instance O.OverloadedMethodInfo RelationPrintMethodInfo Relation where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Relation.relationPrint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Relation.html#v:relationPrint"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRelationMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveRelationMethod "count" o = RelationCountMethodInfo
    ResolveRelationMethod "delete" o = RelationDeleteMethodInfo
    ResolveRelationMethod "destroy" o = RelationDestroyMethodInfo
    ResolveRelationMethod "print" o = RelationPrintMethodInfo
    ResolveRelationMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveRelationMethod t Relation, O.OverloadedMethod info Relation p) => OL.IsLabel t (Relation -> 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 ~ ResolveRelationMethod t Relation, O.OverloadedMethod info Relation p, R.HasField t Relation p) => R.HasField t Relation p where
    getField = O.overloadedMethod @info

#endif

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

#endif