#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
       && !defined(__HADDOCK_VERSION__))
module GI.GLib.Unions.DoubleIEEE754
    (
    DoubleIEEE754(..)                       ,
    newZeroDoubleIEEE754                    ,
    noDoubleIEEE754                         ,
 
#if ENABLE_OVERLOADING
    doubleIEEE754_vDouble                   ,
#endif
    getDoubleIEEE754VDouble                 ,
    setDoubleIEEE754VDouble                 ,
    ) 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.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
newtype DoubleIEEE754 = DoubleIEEE754 (ManagedPtr DoubleIEEE754)
instance WrappedPtr DoubleIEEE754 where
    wrappedPtrCalloc = callocBytes 8
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 8 >=> wrapPtr DoubleIEEE754)
    wrappedPtrFree = Just ptr_to_g_free
newZeroDoubleIEEE754 :: MonadIO m => m DoubleIEEE754
newZeroDoubleIEEE754 = liftIO $ wrappedPtrCalloc >>= wrapPtr DoubleIEEE754
instance tag ~ 'AttrSet => Constructible DoubleIEEE754 tag where
    new _ attrs = do
        o <- newZeroDoubleIEEE754
        GI.Attributes.set o attrs
        return o
noDoubleIEEE754 :: Maybe DoubleIEEE754
noDoubleIEEE754 = Nothing
getDoubleIEEE754VDouble :: MonadIO m => DoubleIEEE754 -> m Double
getDoubleIEEE754VDouble s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CDouble
    let val' = realToFrac val
    return val'
setDoubleIEEE754VDouble :: MonadIO m => DoubleIEEE754 -> Double -> m ()
setDoubleIEEE754VDouble s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 0) (val' :: CDouble)
#if ENABLE_OVERLOADING
data DoubleIEEE754VDoubleFieldInfo
instance AttrInfo DoubleIEEE754VDoubleFieldInfo where
    type AttrAllowedOps DoubleIEEE754VDoubleFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DoubleIEEE754VDoubleFieldInfo = (~) Double
    type AttrBaseTypeConstraint DoubleIEEE754VDoubleFieldInfo = (~) DoubleIEEE754
    type AttrGetType DoubleIEEE754VDoubleFieldInfo = Double
    type AttrLabel DoubleIEEE754VDoubleFieldInfo = "v_double"
    type AttrOrigin DoubleIEEE754VDoubleFieldInfo = DoubleIEEE754
    attrGet _ = getDoubleIEEE754VDouble
    attrSet _ = setDoubleIEEE754VDouble
    attrConstruct = undefined
    attrClear _ = undefined
doubleIEEE754_vDouble :: AttrLabelProxy "vDouble"
doubleIEEE754_vDouble = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList DoubleIEEE754
type instance O.AttributeList DoubleIEEE754 = DoubleIEEE754AttributeList
type DoubleIEEE754AttributeList = ('[ '("vDouble", DoubleIEEE754VDoubleFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveDoubleIEEE754Method (t :: Symbol) (o :: *) :: * where
    ResolveDoubleIEEE754Method l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDoubleIEEE754Method t DoubleIEEE754, O.MethodInfo info DoubleIEEE754 p) => OL.IsLabel t (DoubleIEEE754 -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif