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

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

module GI.Handy.Functions
    ( 

 -- * Methods


-- ** easeOutCubic #method:easeOutCubic#

    easeOutCubic                            ,


-- ** enumValueRowName #method:enumValueRowName#

    enumValueRowName                        ,


-- ** getEnableAnimations #method:getEnableAnimations#

    getEnableAnimations                     ,


-- ** init #method:init#

    init                                    ,




    ) 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.Coerce as Coerce
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 qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Handy.Objects.EnumValueObject as Handy.EnumValueObject

-- function init
-- Args: []
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_init" hdy_init :: 
    IO ()

-- | Call this function just after initializing GTK, if you are using
-- t'GI.Gtk.Objects.Application.Application' it means it must be called when the [startup]("GI.Gio.Objects.Application#g:signal:startup")
-- signal is emitted. If libhandy has already been initialized, the function
-- will simply return.
-- 
-- This makes sure translations, types, themes, and icons for the Handy library
-- are set up properly.
init ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ()
init :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m ()
init  = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    IO ()
hdy_init
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- function get_enable_animations
-- Args: [ Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidget" , 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 "hdy_get_enable_animations" hdy_get_enable_animations :: 
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO CInt

-- | Returns whether animations are enabled for that widget. This should be used
-- when implementing an animated widget to know whether to animate it or not.
-- 
-- /Since: 0.0.11/
getEnableAnimations ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Widget.IsWidget a) =>
    a
    -- ^ /@widget@/: a t'GI.Gtk.Objects.Widget.Widget'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if animations are enabled for /@widget@/.
getEnableAnimations :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWidget a) =>
a -> m Bool
getEnableAnimations a
widget = 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 Widget
widget' <- a -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
widget
    CInt
result <- Ptr Widget -> IO CInt
hdy_get_enable_animations Ptr Widget
widget'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
widget
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'


-- function enum_value_row_name
-- Args: [ Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "EnumValueObject" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the value from the enum from which to get a name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "unused user data" , 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 "hdy_enum_value_row_name" hdy_enum_value_row_name :: 
    Ptr Handy.EnumValueObject.EnumValueObject -> -- value : TInterface (Name {namespace = "Handy", name = "EnumValueObject"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO CString

-- | This is a default implementation of t'GI.Handy.Callbacks.ComboRowGetEnumValueNameFunc' to be
-- used with 'GI.Handy.Objects.ComboRow.comboRowSetForEnum'. If the enumeration has a nickname, it
-- will return it, otherwise it will return its name.
-- 
-- /Since: 0.0.6/
enumValueRowName ::
    (B.CallStack.HasCallStack, MonadIO m, Handy.EnumValueObject.IsEnumValueObject a) =>
    a
    -- ^ /@value@/: the value from the enum from which to get a name
    -> Ptr ()
    -- ^ /@userData@/: unused user data
    -> m T.Text
    -- ^ __Returns:__ a newly allocated displayable name that represents /@value@/
enumValueRowName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEnumValueObject a) =>
a -> Ptr () -> m Text
enumValueRowName a
value Ptr ()
userData = 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 EnumValueObject
value' <- a -> IO (Ptr EnumValueObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
value
    CString
result <- Ptr EnumValueObject -> Ptr () -> IO CString
hdy_enum_value_row_name Ptr EnumValueObject
value' Ptr ()
userData
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"enumValueRowName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
value
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'


-- function ease_out_cubic
-- Args: [ Arg
--           { argCName = "t"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the term" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "hdy_ease_out_cubic" hdy_ease_out_cubic :: 
    CDouble ->                              -- t : TBasicType TDouble
    IO CDouble

-- | Computes the ease out for /@t@/.
-- 
-- /Since: 0.0.11/
easeOutCubic ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Double
    -- ^ /@t@/: the term
    -> m Double
    -- ^ __Returns:__ the ease out for /@t@/.
easeOutCubic :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Double -> m Double
easeOutCubic Double
t = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    let t' :: CDouble
t' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
t
    CDouble
result <- CDouble -> IO CDouble
hdy_ease_out_cubic CDouble
t'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'