{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The @PangoAttrFloat@ structure is used to represent attributes with
-- a float or double value.

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

module GI.Pango.Structs.AttrFloat
    ( 

-- * Exported types
    AttrFloat(..)                           ,
    newZeroAttrFloat                        ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveAttrFloatMethod                  ,
#endif



 -- * Properties


-- ** attr #attr:attr#
-- | the common portion of the attribute

#if defined(ENABLE_OVERLOADING)
    attrFloat_attr                          ,
#endif
    getAttrFloatAttr                        ,


-- ** value #attr:value#
-- | the value of the attribute

#if defined(ENABLE_OVERLOADING)
    attrFloat_value                         ,
#endif
    getAttrFloatValue                       ,
    setAttrFloatValue                       ,




    ) 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 {-# SOURCE #-} qualified GI.Pango.Structs.Attribute as Pango.Attribute

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

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

instance BoxedPtr AttrFloat where
    boxedPtrCopy :: AttrFloat -> IO AttrFloat
boxedPtrCopy = \AttrFloat
p -> forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AttrFloat
p (forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
24 forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr AttrFloat -> AttrFloat
AttrFloat)
    boxedPtrFree :: AttrFloat -> IO ()
boxedPtrFree = \AttrFloat
x -> forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr AttrFloat
x forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr AttrFloat where
    boxedPtrCalloc :: IO (Ptr AttrFloat)
boxedPtrCalloc = forall a. Int -> IO (Ptr a)
callocBytes Int
24


-- | Construct a `AttrFloat` struct initialized to zero.
newZeroAttrFloat :: MonadIO m => m AttrFloat
newZeroAttrFloat :: forall (m :: * -> *). MonadIO m => m AttrFloat
newZeroAttrFloat = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr AttrFloat -> AttrFloat
AttrFloat

instance tag ~ 'AttrSet => Constructible AttrFloat tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr AttrFloat -> AttrFloat)
-> [AttrOp AttrFloat tag] -> m AttrFloat
new ManagedPtr AttrFloat -> AttrFloat
_ [AttrOp AttrFloat tag]
attrs = do
        AttrFloat
o <- forall (m :: * -> *). MonadIO m => m AttrFloat
newZeroAttrFloat
        forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set AttrFloat
o [AttrOp AttrFloat tag]
attrs
        forall (m :: * -> *) a. Monad m => a -> m a
return AttrFloat
o


-- | Get the value of the “@attr@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' attrFloat #attr
-- @
getAttrFloatAttr :: MonadIO m => AttrFloat -> m Pango.Attribute.Attribute
getAttrFloatAttr :: forall (m :: * -> *). MonadIO m => AttrFloat -> m Attribute
getAttrFloatAttr AttrFloat
s = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrFloat
s forall a b. (a -> b) -> a -> b
$ \Ptr AttrFloat
ptr -> do
    let val :: Ptr Attribute
val = Ptr AttrFloat
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: (Ptr Pango.Attribute.Attribute)
    Attribute
val' <- (forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) Ptr Attribute
val
    forall (m :: * -> *) a. Monad m => a -> m a
return Attribute
val'

#if defined(ENABLE_OVERLOADING)
data AttrFloatAttrFieldInfo
instance AttrInfo AttrFloatAttrFieldInfo where
    type AttrBaseTypeConstraint AttrFloatAttrFieldInfo = (~) AttrFloat
    type AttrAllowedOps AttrFloatAttrFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint AttrFloatAttrFieldInfo = (~) (Ptr Pango.Attribute.Attribute)
    type AttrTransferTypeConstraint AttrFloatAttrFieldInfo = (~)(Ptr Pango.Attribute.Attribute)
    type AttrTransferType AttrFloatAttrFieldInfo = (Ptr Pango.Attribute.Attribute)
    type AttrGetType AttrFloatAttrFieldInfo = Pango.Attribute.Attribute
    type AttrLabel AttrFloatAttrFieldInfo = "attr"
    type AttrOrigin AttrFloatAttrFieldInfo = AttrFloat
    attrGet = getAttrFloatAttr
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrFloat.attr"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.27/docs/GI-Pango-Structs-AttrFloat.html#g:attr:attr"
        })

attrFloat_attr :: AttrLabelProxy "attr"
attrFloat_attr = AttrLabelProxy

#endif


-- | Get the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' attrFloat #value
-- @
getAttrFloatValue :: MonadIO m => AttrFloat -> m Double
getAttrFloatValue :: forall (m :: * -> *). MonadIO m => AttrFloat -> m Double
getAttrFloatValue AttrFloat
s = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrFloat
s forall a b. (a -> b) -> a -> b
$ \Ptr AttrFloat
ptr -> do
    CDouble
val <- forall a. Storable a => Ptr a -> IO a
peek (Ptr AttrFloat
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO CDouble
    let val' :: Double
val' = forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' attrFloat [ #value 'Data.GI.Base.Attributes.:=' value ]
-- @
setAttrFloatValue :: MonadIO m => AttrFloat -> Double -> m ()
setAttrFloatValue :: forall (m :: * -> *). MonadIO m => AttrFloat -> Double -> m ()
setAttrFloatValue AttrFloat
s Double
val = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrFloat
s forall a b. (a -> b) -> a -> b
$ \Ptr AttrFloat
ptr -> do
    let val' :: CDouble
val' = forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrFloat
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data AttrFloatValueFieldInfo
instance AttrInfo AttrFloatValueFieldInfo where
    type AttrBaseTypeConstraint AttrFloatValueFieldInfo = (~) AttrFloat
    type AttrAllowedOps AttrFloatValueFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint AttrFloatValueFieldInfo = (~) Double
    type AttrTransferTypeConstraint AttrFloatValueFieldInfo = (~)Double
    type AttrTransferType AttrFloatValueFieldInfo = Double
    type AttrGetType AttrFloatValueFieldInfo = Double
    type AttrLabel AttrFloatValueFieldInfo = "value"
    type AttrOrigin AttrFloatValueFieldInfo = AttrFloat
    attrGet = getAttrFloatValue
    attrSet = setAttrFloatValue
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Structs.AttrFloat.value"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.27/docs/GI-Pango-Structs-AttrFloat.html#g:attr:value"
        })

attrFloat_value :: AttrLabelProxy "value"
attrFloat_value = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AttrFloat
type instance O.AttributeList AttrFloat = AttrFloatAttributeList
type AttrFloatAttributeList = ('[ '("attr", AttrFloatAttrFieldInfo), '("value", AttrFloatValueFieldInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAttrFloatMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveAttrFloatMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif