{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Fixed point number using a (16.16) notation.

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

module GI.Cogl.Objects.Fixed
    ( 

-- * Exported types
    Fixed(..)                               ,
    IsFixed                                 ,
    toFixed                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [pow2]("GI.Cogl.Objects.Fixed#g:method:pow2").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveFixedMethod                      ,
#endif

-- ** pow #method:pow#

    fixedPow                                ,


-- ** pow2 #method:pow2#

#if defined(ENABLE_OVERLOADING)
    FixedPow2MethodInfo                     ,
#endif
    fixedPow2                               ,




    ) 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


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

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

foreign import ccall "cogl_fixed_get_type"
    c_cogl_fixed_get_type :: IO B.Types.GType

instance B.Types.TypedObject Fixed where
    glibType :: IO GType
glibType = IO GType
c_cogl_fixed_get_type

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

instance O.HasParentTypes Fixed
type instance O.ParentTypes Fixed = '[]

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

--- XXX Missing getter and/or setter, so no GValue instance could be generated.
#if defined(ENABLE_OVERLOADING)
type family ResolveFixedMethod (t :: Symbol) (o :: *) :: * where
    ResolveFixedMethod "pow2" o = FixedPow2MethodInfo
    ResolveFixedMethod l o = O.MethodResolutionFailed l o

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

#endif

instance (info ~ ResolveFixedMethod t Fixed, O.OverloadedMethodInfo info Fixed) => OL.IsLabel t (O.MethodProxy info Fixed) 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 Fixed where
    boxedPtrCopy :: Fixed -> IO Fixed
boxedPtrCopy = Fixed -> IO Fixed
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: Fixed -> IO ()
boxedPtrFree = \Fixed
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- method Fixed::pow2
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "x"
--           , argType = TInterface Name { namespace = "Cogl" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #CoglFixed number"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "cogl_fixed_pow2" cogl_fixed_pow2 :: 
    Ptr Fixed ->                            -- x : TInterface (Name {namespace = "Cogl", name = "Fixed"})
    IO Word32

-- | Calculates 2 to the /@x@/ power.
-- 
-- This function is around 11 times faster on x86, and around 22 times faster
-- on fpu-less arm than libc pow(2, x).
-- 
-- /Since: 1.0/
fixedPow2 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a) =>
    a
    -- ^ /@x@/: a @/CoglFixed/@ number
    -> m Word32
    -- ^ __Returns:__ the power of 2 to the passed value
fixedPow2 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFixed a) =>
a -> m Word32
fixedPow2 a
x = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Fixed
x' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
x
    Word32
result <- Ptr Fixed -> IO Word32
cogl_fixed_pow2 Ptr Fixed
x'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
x
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data FixedPow2MethodInfo
instance (signature ~ (m Word32), MonadIO m, IsFixed a) => O.OverloadedMethod FixedPow2MethodInfo a signature where
    overloadedMethod = fixedPow2

instance O.OverloadedMethodInfo FixedPow2MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Cogl.Objects.Fixed.fixedPow2",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-cogl-1.0.2/docs/GI-Cogl-Objects-Fixed.html#v:fixedPow2"
        })


#endif

-- method Fixed::pow
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "x"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "base" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TInterface Name { namespace = "Cogl" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#CoglFixed exponent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "cogl_fixed_pow" cogl_fixed_pow :: 
    Word32 ->                               -- x : TBasicType TUInt
    Ptr Fixed ->                            -- y : TInterface (Name {namespace = "Cogl", name = "Fixed"})
    IO Word32

-- | Calculates /@x@/ to the /@y@/ power.
-- 
-- /Since: 1.0/
fixedPow ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a) =>
    Word32
    -- ^ /@x@/: base
    -> a
    -- ^ /@y@/: @/CoglFixed/@ exponent
    -> m Word32
    -- ^ __Returns:__ the power of /@x@/ to the /@y@/
fixedPow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFixed a) =>
Word32 -> a -> m Word32
fixedPow Word32
x a
y = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Fixed
y' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
y
    Word32
result <- Word32 -> Ptr Fixed -> IO Word32
cogl_fixed_pow Word32
x Ptr Fixed
y'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
y
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
#endif