{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A GPatternSpec struct is the \'compiled\' form of a pattern. This
-- structure is opaque and its fields cannot be accessed directly.

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

module GI.GLib.Structs.PatternSpec
    ( 

-- * Exported types
    PatternSpec(..)                         ,
    noPatternSpec                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolvePatternSpecMethod                ,
#endif


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    PatternSpecEqualMethodInfo              ,
#endif
    patternSpecEqual                        ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    PatternSpecFreeMethodInfo               ,
#endif
    patternSpecFree                         ,




    ) 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


-- | Memory-managed wrapper type.
newtype PatternSpec = PatternSpec (ManagedPtr PatternSpec)
    deriving (PatternSpec -> PatternSpec -> Bool
(PatternSpec -> PatternSpec -> Bool)
-> (PatternSpec -> PatternSpec -> Bool) -> Eq PatternSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PatternSpec -> PatternSpec -> Bool
$c/= :: PatternSpec -> PatternSpec -> Bool
== :: PatternSpec -> PatternSpec -> Bool
$c== :: PatternSpec -> PatternSpec -> Bool
Eq)
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance WrappedPtr PatternSpec where
    wrappedPtrCalloc :: IO (Ptr PatternSpec)
wrappedPtrCalloc = Ptr PatternSpec -> IO (Ptr PatternSpec)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PatternSpec
forall a. Ptr a
nullPtr
    wrappedPtrCopy :: PatternSpec -> IO PatternSpec
wrappedPtrCopy = PatternSpec -> IO PatternSpec
forall (m :: * -> *) a. Monad m => a -> m a
return
    wrappedPtrFree :: Maybe (GDestroyNotify PatternSpec)
wrappedPtrFree = Maybe (GDestroyNotify PatternSpec)
forall a. Maybe a
Nothing

-- | A convenience alias for `Nothing` :: `Maybe` `PatternSpec`.
noPatternSpec :: Maybe PatternSpec
noPatternSpec :: Maybe PatternSpec
noPatternSpec = Maybe PatternSpec
forall a. Maybe a
Nothing


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

-- method PatternSpec::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pspec1"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "PatternSpec" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GPatternSpec" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pspec2"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "PatternSpec" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GPatternSpec"
--                 , 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_pattern_spec_equal" g_pattern_spec_equal :: 
    Ptr PatternSpec ->                      -- pspec1 : TInterface (Name {namespace = "GLib", name = "PatternSpec"})
    Ptr PatternSpec ->                      -- pspec2 : TInterface (Name {namespace = "GLib", name = "PatternSpec"})
    IO CInt

-- | Compares two compiled pattern specs and returns whether they will
-- match the same set of strings.
patternSpecEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    PatternSpec
    -- ^ /@pspec1@/: a t'GI.GLib.Structs.PatternSpec.PatternSpec'
    -> PatternSpec
    -- ^ /@pspec2@/: another t'GI.GLib.Structs.PatternSpec.PatternSpec'
    -> m Bool
    -- ^ __Returns:__ Whether the compiled patterns are equal
patternSpecEqual :: PatternSpec -> PatternSpec -> m Bool
patternSpecEqual pspec1 :: PatternSpec
pspec1 pspec2 :: PatternSpec
pspec2 = 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 PatternSpec
pspec1' <- PatternSpec -> IO (Ptr PatternSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PatternSpec
pspec1
    Ptr PatternSpec
pspec2' <- PatternSpec -> IO (Ptr PatternSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PatternSpec
pspec2
    CInt
result <- Ptr PatternSpec -> Ptr PatternSpec -> IO CInt
g_pattern_spec_equal Ptr PatternSpec
pspec1' Ptr PatternSpec
pspec2'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    PatternSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PatternSpec
pspec1
    PatternSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PatternSpec
pspec2
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PatternSpecEqualMethodInfo
instance (signature ~ (PatternSpec -> m Bool), MonadIO m) => O.MethodInfo PatternSpecEqualMethodInfo PatternSpec signature where
    overloadedMethod = patternSpecEqual

#endif

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

foreign import ccall "g_pattern_spec_free" g_pattern_spec_free :: 
    Ptr PatternSpec ->                      -- pspec : TInterface (Name {namespace = "GLib", name = "PatternSpec"})
    IO ()

-- | Frees the memory allocated for the t'GI.GLib.Structs.PatternSpec.PatternSpec'.
patternSpecFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    PatternSpec
    -- ^ /@pspec@/: a t'GI.GLib.Structs.PatternSpec.PatternSpec'
    -> m ()
patternSpecFree :: PatternSpec -> m ()
patternSpecFree pspec :: PatternSpec
pspec = 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 PatternSpec
pspec' <- PatternSpec -> IO (Ptr PatternSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PatternSpec
pspec
    Ptr PatternSpec -> IO ()
g_pattern_spec_free Ptr PatternSpec
pspec'
    PatternSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PatternSpec
pspec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PatternSpecFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo PatternSpecFreeMethodInfo PatternSpec signature where
    overloadedMethod = patternSpecFree

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolvePatternSpecMethod (t :: Symbol) (o :: *) :: * where
    ResolvePatternSpecMethod "equal" o = PatternSpecEqualMethodInfo
    ResolvePatternSpecMethod "free" o = PatternSpecFreeMethodInfo
    ResolvePatternSpecMethod l o = O.MethodResolutionFailed l o

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

#endif