{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gtk.Objects.ClosureExpression
    ( 

-- * Exported types
    ClosureExpression(..)                   ,
    IsClosureExpression                     ,
    toClosureExpression                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bind]("GI.Gtk.Objects.Expression#g:method:bind"), [evaluate]("GI.Gtk.Objects.Expression#g:method:evaluate"), [isStatic]("GI.Gtk.Objects.Expression#g:method:isStatic"), [ref]("GI.Gtk.Objects.Expression#g:method:ref"), [unref]("GI.Gtk.Objects.Expression#g:method:unref"), [watch]("GI.Gtk.Objects.Expression#g:method:watch").
-- 
-- ==== Getters
-- [getValueType]("GI.Gtk.Objects.Expression#g:method:getValueType").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveClosureExpressionMethod          ,
#endif

-- ** new #method:new#

    closureExpressionNew                    ,




    ) 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

import {-# SOURCE #-} qualified GI.Gtk.Objects.Expression as Gtk.Expression

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

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

foreign import ccall "gtk_closure_expression_get_type"
    c_gtk_closure_expression_get_type :: IO B.Types.GType

instance B.Types.TypedObject ClosureExpression where
    glibType :: IO GType
glibType = IO GType
c_gtk_closure_expression_get_type

-- | Type class for types which can be safely cast to `ClosureExpression`, for instance with `toClosureExpression`.
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf ClosureExpression o) => IsClosureExpression o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf ClosureExpression o) => IsClosureExpression o

instance O.HasParentTypes ClosureExpression
type instance O.ParentTypes ClosureExpression = '[Gtk.Expression.Expression]

-- | Cast to `ClosureExpression`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toClosureExpression :: (MIO.MonadIO m, IsClosureExpression o) => o -> m ClosureExpression
toClosureExpression :: forall (m :: * -> *) o.
(MonadIO m, IsClosureExpression o) =>
o -> m ClosureExpression
toClosureExpression = IO ClosureExpression -> m ClosureExpression
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ClosureExpression -> m ClosureExpression)
-> (o -> IO ClosureExpression) -> o -> m ClosureExpression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ClosureExpression -> ClosureExpression)
-> o -> IO ClosureExpression
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ClosureExpression -> ClosureExpression
ClosureExpression

--- XXX Missing getter and/or setter, so no GValue instance could be generated.
#if defined(ENABLE_OVERLOADING)
type family ResolveClosureExpressionMethod (t :: Symbol) (o :: *) :: * where
    ResolveClosureExpressionMethod "bind" o = Gtk.Expression.ExpressionBindMethodInfo
    ResolveClosureExpressionMethod "evaluate" o = Gtk.Expression.ExpressionEvaluateMethodInfo
    ResolveClosureExpressionMethod "isStatic" o = Gtk.Expression.ExpressionIsStaticMethodInfo
    ResolveClosureExpressionMethod "ref" o = Gtk.Expression.ExpressionRefMethodInfo
    ResolveClosureExpressionMethod "unref" o = Gtk.Expression.ExpressionUnrefMethodInfo
    ResolveClosureExpressionMethod "watch" o = Gtk.Expression.ExpressionWatchMethodInfo
    ResolveClosureExpressionMethod "getValueType" o = Gtk.Expression.ExpressionGetValueTypeMethodInfo
    ResolveClosureExpressionMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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


-- method ClosureExpression::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "value_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the type of the value that this expression evaluates to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "closure"
--           , argType = TGClosure Nothing
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "closure to call when evaluating this expression. If closure is floating, it is adopted"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_params"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of params needed for evaluating @closure"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "params"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gtk" , name = "Expression" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "expressions for each parameter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_params"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "the number of params needed for evaluating @closure"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Expression" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_closure_expression_new" gtk_closure_expression_new :: 
    CGType ->                               -- value_type : TBasicType TGType
    Ptr (GClosure ()) ->                    -- closure : TGClosure Nothing
    Word32 ->                               -- n_params : TBasicType TUInt
    Ptr (Ptr Gtk.Expression.Expression) ->  -- params : TCArray False (-1) 2 (TInterface (Name {namespace = "Gtk", name = "Expression"}))
    IO (Ptr Gtk.Expression.Expression)

-- | Creates a GtkExpression that calls /@closure@/ when it is evaluated.
-- /@closure@/ is called with the /@this@/ object and the results of evaluating
-- the /@params@/ expressions.
closureExpressionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GType
    -- ^ /@valueType@/: the type of the value that this expression evaluates to
    -> GClosure a
    -- ^ /@closure@/: closure to call when evaluating this expression. If closure is floating, it is adopted
    -> Maybe ([Gtk.Expression.Expression])
    -- ^ /@params@/: expressions for each parameter
    -> m Gtk.Expression.Expression
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Expression.Expression'
closureExpressionNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m) =>
GType -> GClosure a -> Maybe [Expression] -> m Expression
closureExpressionNew GType
valueType GClosure a
closure Maybe [Expression]
params = IO Expression -> m Expression
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Expression -> m Expression) -> IO Expression -> m Expression
forall a b. (a -> b) -> a -> b
$ do
    let nParams :: Word32
nParams = case Maybe [Expression]
params of
            Maybe [Expression]
Nothing -> Word32
0
            Just [Expression]
jParams -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Expression] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Expression]
jParams
    let valueType' :: CGType
valueType' = GType -> CGType
gtypeToCGType GType
valueType
    Ptr (GClosure ())
closure' <- GClosure a -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure a
closure
    Ptr (Ptr Expression)
maybeParams <- case Maybe [Expression]
params of
        Maybe [Expression]
Nothing -> Ptr (Ptr Expression) -> IO (Ptr (Ptr Expression))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr Expression)
forall a. Ptr a
nullPtr
        Just [Expression]
jParams -> do
            [Ptr Expression]
jParams' <- (Expression -> IO (Ptr Expression))
-> [Expression] -> IO [Ptr Expression]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Expression -> IO (Ptr Expression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
B.ManagedPtr.disownManagedPtr [Expression]
jParams
            Ptr (Ptr Expression)
jParams'' <- [Ptr Expression] -> IO (Ptr (Ptr Expression))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packPtrArray [Ptr Expression]
jParams'
            Ptr (Ptr Expression) -> IO (Ptr (Ptr Expression))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr Expression)
jParams''
    Ptr Expression
result <- CGType
-> Ptr (GClosure ())
-> Word32
-> Ptr (Ptr Expression)
-> IO (Ptr Expression)
gtk_closure_expression_new CGType
valueType' Ptr (GClosure ())
closure' Word32
nParams Ptr (Ptr Expression)
maybeParams
    Text -> Ptr Expression -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"closureExpressionNew" Ptr Expression
result
    Expression
result' <- ((ManagedPtr Expression -> Expression)
-> Ptr Expression -> IO Expression
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Expression -> Expression
Gtk.Expression.Expression) Ptr Expression
result
    GClosure a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure a
closure
    Maybe [Expression] -> ([Expression] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [Expression]
params ((Expression -> IO ()) -> [Expression] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Expression -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
    Expression -> IO Expression
forall (m :: * -> *) a. Monad m => a -> m a
return Expression
result'

#if defined(ENABLE_OVERLOADING)
#endif