{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

Structure describing the color info.
-}

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

module GI.GstVideo.Structs.VideoColorimetry
    (

-- * Exported types
    VideoColorimetry(..)                    ,
    newZeroVideoColorimetry                 ,
    noVideoColorimetry                      ,


 -- * Methods
-- ** fromString #method:fromString#

#if ENABLE_OVERLOADING
    VideoColorimetryFromStringMethodInfo    ,
#endif
    videoColorimetryFromString              ,


-- ** isEqual #method:isEqual#

#if ENABLE_OVERLOADING
    VideoColorimetryIsEqualMethodInfo       ,
#endif
    videoColorimetryIsEqual                 ,


-- ** matches #method:matches#

#if ENABLE_OVERLOADING
    VideoColorimetryMatchesMethodInfo       ,
#endif
    videoColorimetryMatches                 ,


-- ** toString #method:toString#

#if ENABLE_OVERLOADING
    VideoColorimetryToStringMethodInfo      ,
#endif
    videoColorimetryToString                ,




 -- * Properties
-- ** matrix #attr:matrix#
{- | the color matrix. Used to convert between Y\'PbPr and
         non-linear RGB (R\'G\'B\')
-}
    getVideoColorimetryMatrix               ,
    setVideoColorimetryMatrix               ,
#if ENABLE_OVERLOADING
    videoColorimetry_matrix                 ,
#endif


-- ** primaries #attr:primaries#
{- | color primaries. used to convert between R\'G\'B\' and CIE XYZ
-}
    getVideoColorimetryPrimaries            ,
    setVideoColorimetryPrimaries            ,
#if ENABLE_OVERLOADING
    videoColorimetry_primaries              ,
#endif


-- ** range #attr:range#
{- | the color range. This is the valid range for the samples.
        It is used to convert the samples to Y\'PbPr values.
-}
    getVideoColorimetryRange                ,
    setVideoColorimetryRange                ,
#if ENABLE_OVERLOADING
    videoColorimetry_range                  ,
#endif


-- ** transfer #attr:transfer#
{- | the transfer function. used to convert between R\'G\'B\' and RGB
-}
    getVideoColorimetryTransfer             ,
    setVideoColorimetryTransfer             ,
#if ENABLE_OVERLOADING
    videoColorimetry_transfer               ,
#endif




    ) 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

import {-# SOURCE #-} qualified GI.GstVideo.Enums as GstVideo.Enums

-- | Memory-managed wrapper type.
newtype VideoColorimetry = VideoColorimetry (ManagedPtr VideoColorimetry)
instance WrappedPtr VideoColorimetry where
    wrappedPtrCalloc = callocBytes 16
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 16 >=> wrapPtr VideoColorimetry)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `VideoColorimetry` struct initialized to zero.
newZeroVideoColorimetry :: MonadIO m => m VideoColorimetry
newZeroVideoColorimetry = liftIO $ wrappedPtrCalloc >>= wrapPtr VideoColorimetry

instance tag ~ 'AttrSet => Constructible VideoColorimetry tag where
    new _ attrs = do
        o <- newZeroVideoColorimetry
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `VideoColorimetry`.
noVideoColorimetry :: Maybe VideoColorimetry
noVideoColorimetry = Nothing

{- |
Get the value of the “@range@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' videoColorimetry #range
@
-}
getVideoColorimetryRange :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoColorRange
getVideoColorimetryRange s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

{- |
Set the value of the “@range@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' videoColorimetry [ #range 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoColorimetryRange :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoColorRange -> m ()
setVideoColorimetryRange s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if ENABLE_OVERLOADING
data VideoColorimetryRangeFieldInfo
instance AttrInfo VideoColorimetryRangeFieldInfo where
    type AttrAllowedOps VideoColorimetryRangeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryRangeFieldInfo = (~) GstVideo.Enums.VideoColorRange
    type AttrBaseTypeConstraint VideoColorimetryRangeFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryRangeFieldInfo = GstVideo.Enums.VideoColorRange
    type AttrLabel VideoColorimetryRangeFieldInfo = "range"
    type AttrOrigin VideoColorimetryRangeFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryRange
    attrSet _ = setVideoColorimetryRange
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_range :: AttrLabelProxy "range"
videoColorimetry_range = AttrLabelProxy

#endif


{- |
Get the value of the “@matrix@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' videoColorimetry #matrix
@
-}
getVideoColorimetryMatrix :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoColorMatrix
getVideoColorimetryMatrix s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

{- |
Set the value of the “@matrix@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' videoColorimetry [ #matrix 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoColorimetryMatrix :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoColorMatrix -> m ()
setVideoColorimetryMatrix s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 4) (val' :: CUInt)

#if ENABLE_OVERLOADING
data VideoColorimetryMatrixFieldInfo
instance AttrInfo VideoColorimetryMatrixFieldInfo where
    type AttrAllowedOps VideoColorimetryMatrixFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryMatrixFieldInfo = (~) GstVideo.Enums.VideoColorMatrix
    type AttrBaseTypeConstraint VideoColorimetryMatrixFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryMatrixFieldInfo = GstVideo.Enums.VideoColorMatrix
    type AttrLabel VideoColorimetryMatrixFieldInfo = "matrix"
    type AttrOrigin VideoColorimetryMatrixFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryMatrix
    attrSet _ = setVideoColorimetryMatrix
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_matrix :: AttrLabelProxy "matrix"
videoColorimetry_matrix = AttrLabelProxy

#endif


{- |
Get the value of the “@transfer@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' videoColorimetry #transfer
@
-}
getVideoColorimetryTransfer :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoTransferFunction
getVideoColorimetryTransfer s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

{- |
Set the value of the “@transfer@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' videoColorimetry [ #transfer 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoColorimetryTransfer :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoTransferFunction -> m ()
setVideoColorimetryTransfer s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 8) (val' :: CUInt)

#if ENABLE_OVERLOADING
data VideoColorimetryTransferFieldInfo
instance AttrInfo VideoColorimetryTransferFieldInfo where
    type AttrAllowedOps VideoColorimetryTransferFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryTransferFieldInfo = (~) GstVideo.Enums.VideoTransferFunction
    type AttrBaseTypeConstraint VideoColorimetryTransferFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryTransferFieldInfo = GstVideo.Enums.VideoTransferFunction
    type AttrLabel VideoColorimetryTransferFieldInfo = "transfer"
    type AttrOrigin VideoColorimetryTransferFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryTransfer
    attrSet _ = setVideoColorimetryTransfer
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_transfer :: AttrLabelProxy "transfer"
videoColorimetry_transfer = AttrLabelProxy

#endif


{- |
Get the value of the “@primaries@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' videoColorimetry #primaries
@
-}
getVideoColorimetryPrimaries :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoColorPrimaries
getVideoColorimetryPrimaries s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

{- |
Set the value of the “@primaries@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' videoColorimetry [ #primaries 'Data.GI.Base.Attributes.:=' value ]
@
-}
setVideoColorimetryPrimaries :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoColorPrimaries -> m ()
setVideoColorimetryPrimaries s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 12) (val' :: CUInt)

#if ENABLE_OVERLOADING
data VideoColorimetryPrimariesFieldInfo
instance AttrInfo VideoColorimetryPrimariesFieldInfo where
    type AttrAllowedOps VideoColorimetryPrimariesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryPrimariesFieldInfo = (~) GstVideo.Enums.VideoColorPrimaries
    type AttrBaseTypeConstraint VideoColorimetryPrimariesFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryPrimariesFieldInfo = GstVideo.Enums.VideoColorPrimaries
    type AttrLabel VideoColorimetryPrimariesFieldInfo = "primaries"
    type AttrOrigin VideoColorimetryPrimariesFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryPrimaries
    attrSet _ = setVideoColorimetryPrimaries
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_primaries :: AttrLabelProxy "primaries"
videoColorimetry_primaries = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList VideoColorimetry
type instance O.AttributeList VideoColorimetry = VideoColorimetryAttributeList
type VideoColorimetryAttributeList = ('[ '("range", VideoColorimetryRangeFieldInfo), '("matrix", VideoColorimetryMatrixFieldInfo), '("transfer", VideoColorimetryTransferFieldInfo), '("primaries", VideoColorimetryPrimariesFieldInfo)] :: [(Symbol, *)])
#endif

-- method VideoColorimetry::from_string
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoColorimetry", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "color", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a colorimetry string", 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 "gst_video_colorimetry_from_string" gst_video_colorimetry_from_string ::
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    CString ->                              -- color : TBasicType TUTF8
    IO CInt

{- |
Parse the colorimetry string and update /@cinfo@/ with the parsed
values.
-}
videoColorimetryFromString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> T.Text
    {- ^ /@color@/: a colorimetry string -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@color@/ points to valid colorimetry info. -}
videoColorimetryFromString cinfo color = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    color' <- textToCString color
    result <- gst_video_colorimetry_from_string cinfo' color'
    let result' = (/= 0) result
    touchManagedPtr cinfo
    freeMem color'
    return result'

#if ENABLE_OVERLOADING
data VideoColorimetryFromStringMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo VideoColorimetryFromStringMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryFromString

#endif

-- method VideoColorimetry::is_equal
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoColorimetry", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "other", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "another #GstVideoColorimetry", 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 "gst_video_colorimetry_is_equal" gst_video_colorimetry_is_equal ::
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    Ptr VideoColorimetry ->                 -- other : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    IO CInt

{- |
Compare the 2 colorimetry sets for equality

/Since: 1.6/
-}
videoColorimetryIsEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> VideoColorimetry
    {- ^ /@other@/: another 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@cinfo@/ and /@other@/ are equal. -}
videoColorimetryIsEqual cinfo other = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    other' <- unsafeManagedPtrGetPtr other
    result <- gst_video_colorimetry_is_equal cinfo' other'
    let result' = (/= 0) result
    touchManagedPtr cinfo
    touchManagedPtr other
    return result'

#if ENABLE_OVERLOADING
data VideoColorimetryIsEqualMethodInfo
instance (signature ~ (VideoColorimetry -> m Bool), MonadIO m) => O.MethodInfo VideoColorimetryIsEqualMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryIsEqual

#endif

-- method VideoColorimetry::matches
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "color", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a colorimetry string", 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 "gst_video_colorimetry_matches" gst_video_colorimetry_matches ::
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    CString ->                              -- color : TBasicType TUTF8
    IO CInt

{- |
Check if the colorimetry information in /@info@/ matches that of the
string /@color@/.
-}
videoColorimetryMatches ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoInfo.VideoInfo' -}
    -> T.Text
    {- ^ /@color@/: a colorimetry string -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@color@/ conveys the same colorimetry info as the color
information in /@info@/. -}
videoColorimetryMatches cinfo color = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    color' <- textToCString color
    result <- gst_video_colorimetry_matches cinfo' color'
    let result' = (/= 0) result
    touchManagedPtr cinfo
    freeMem color'
    return result'

#if ENABLE_OVERLOADING
data VideoColorimetryMatchesMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo VideoColorimetryMatchesMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryMatches

#endif

-- method VideoColorimetry::to_string
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoColorimetry", 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 "gst_video_colorimetry_to_string" gst_video_colorimetry_to_string ::
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    IO CString

{- |
Make a string representation of /@cinfo@/.
-}
videoColorimetryToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> m T.Text
    {- ^ __Returns:__ a string representation of /@cinfo@/. -}
videoColorimetryToString cinfo = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    result <- gst_video_colorimetry_to_string cinfo'
    checkUnexpectedReturnNULL "videoColorimetryToString" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr cinfo
    return result'

#if ENABLE_OVERLOADING
data VideoColorimetryToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo VideoColorimetryToStringMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryToString

#endif

#if ENABLE_OVERLOADING
type family ResolveVideoColorimetryMethod (t :: Symbol) (o :: *) :: * where
    ResolveVideoColorimetryMethod "fromString" o = VideoColorimetryFromStringMethodInfo
    ResolveVideoColorimetryMethod "isEqual" o = VideoColorimetryIsEqualMethodInfo
    ResolveVideoColorimetryMethod "matches" o = VideoColorimetryMatchesMethodInfo
    ResolveVideoColorimetryMethod "toString" o = VideoColorimetryToStringMethodInfo
    ResolveVideoColorimetryMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveVideoColorimetryMethod t VideoColorimetry, O.MethodInfo info VideoColorimetry p) => OL.IsLabel t (VideoColorimetry -> 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