#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.GObject.Structs.TypeInfo
(
TypeInfo(..) ,
newZeroTypeInfo ,
noTypeInfo ,
clearTypeInfoBaseFinalize ,
getTypeInfoBaseFinalize ,
setTypeInfoBaseFinalize ,
#if ENABLE_OVERLOADING
typeInfo_baseFinalize ,
#endif
clearTypeInfoBaseInit ,
getTypeInfoBaseInit ,
setTypeInfoBaseInit ,
#if ENABLE_OVERLOADING
typeInfo_baseInit ,
#endif
clearTypeInfoClassData ,
getTypeInfoClassData ,
setTypeInfoClassData ,
#if ENABLE_OVERLOADING
typeInfo_classData ,
#endif
clearTypeInfoClassFinalize ,
getTypeInfoClassFinalize ,
setTypeInfoClassFinalize ,
#if ENABLE_OVERLOADING
typeInfo_classFinalize ,
#endif
clearTypeInfoClassInit ,
getTypeInfoClassInit ,
setTypeInfoClassInit ,
#if ENABLE_OVERLOADING
typeInfo_classInit ,
#endif
getTypeInfoClassSize ,
setTypeInfoClassSize ,
#if ENABLE_OVERLOADING
typeInfo_classSize ,
#endif
clearTypeInfoInstanceInit ,
getTypeInfoInstanceInit ,
setTypeInfoInstanceInit ,
#if ENABLE_OVERLOADING
typeInfo_instanceInit ,
#endif
getTypeInfoInstanceSize ,
setTypeInfoInstanceSize ,
#if ENABLE_OVERLOADING
typeInfo_instanceSize ,
#endif
getTypeInfoNPreallocs ,
setTypeInfoNPreallocs ,
#if ENABLE_OVERLOADING
typeInfo_nPreallocs ,
#endif
clearTypeInfoValueTable ,
getTypeInfoValueTable ,
setTypeInfoValueTable ,
#if ENABLE_OVERLOADING
typeInfo_valueTable ,
#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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GI.GObject.Callbacks as GObject.Callbacks
import {-# SOURCE #-} qualified GI.GObject.Structs.TypeValueTable as GObject.TypeValueTable
newtype TypeInfo = TypeInfo (ManagedPtr TypeInfo)
instance WrappedPtr TypeInfo where
wrappedPtrCalloc = callocBytes 72
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 72 >=> wrapPtr TypeInfo)
wrappedPtrFree = Just ptr_to_g_free
newZeroTypeInfo :: MonadIO m => m TypeInfo
newZeroTypeInfo = liftIO $ wrappedPtrCalloc >>= wrapPtr TypeInfo
instance tag ~ 'AttrSet => Constructible TypeInfo tag where
new _ attrs = do
o <- newZeroTypeInfo
GI.Attributes.set o attrs
return o
noTypeInfo :: Maybe TypeInfo
noTypeInfo = Nothing
getTypeInfoClassSize :: MonadIO m => TypeInfo -> m Word16
getTypeInfoClassSize s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO Word16
return val
setTypeInfoClassSize :: MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoClassSize s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (val :: Word16)
#if ENABLE_OVERLOADING
data TypeInfoClassSizeFieldInfo
instance AttrInfo TypeInfoClassSizeFieldInfo where
type AttrAllowedOps TypeInfoClassSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TypeInfoClassSizeFieldInfo = (~) Word16
type AttrBaseTypeConstraint TypeInfoClassSizeFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoClassSizeFieldInfo = Word16
type AttrLabel TypeInfoClassSizeFieldInfo = "class_size"
type AttrOrigin TypeInfoClassSizeFieldInfo = TypeInfo
attrGet _ = getTypeInfoClassSize
attrSet _ = setTypeInfoClassSize
attrConstruct = undefined
attrClear _ = undefined
typeInfo_classSize :: AttrLabelProxy "classSize"
typeInfo_classSize = AttrLabelProxy
#endif
getTypeInfoBaseInit :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.BaseInitFunc)
getTypeInfoBaseInit s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO (FunPtr GObject.Callbacks.C_BaseInitFunc)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GObject.Callbacks.dynamic_BaseInitFunc val'
return val''
return result
setTypeInfoBaseInit :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_BaseInitFunc -> m ()
setTypeInfoBaseInit s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: FunPtr GObject.Callbacks.C_BaseInitFunc)
clearTypeInfoBaseInit :: MonadIO m => TypeInfo -> m ()
clearTypeInfoBaseInit s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_BaseInitFunc)
#if ENABLE_OVERLOADING
data TypeInfoBaseInitFieldInfo
instance AttrInfo TypeInfoBaseInitFieldInfo where
type AttrAllowedOps TypeInfoBaseInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeInfoBaseInitFieldInfo = (~) (FunPtr GObject.Callbacks.C_BaseInitFunc)
type AttrBaseTypeConstraint TypeInfoBaseInitFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoBaseInitFieldInfo = Maybe GObject.Callbacks.BaseInitFunc
type AttrLabel TypeInfoBaseInitFieldInfo = "base_init"
type AttrOrigin TypeInfoBaseInitFieldInfo = TypeInfo
attrGet _ = getTypeInfoBaseInit
attrSet _ = setTypeInfoBaseInit
attrConstruct = undefined
attrClear _ = clearTypeInfoBaseInit
typeInfo_baseInit :: AttrLabelProxy "baseInit"
typeInfo_baseInit = AttrLabelProxy
#endif
getTypeInfoBaseFinalize :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.BaseFinalizeFunc)
getTypeInfoBaseFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO (FunPtr GObject.Callbacks.C_BaseFinalizeFunc)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GObject.Callbacks.dynamic_BaseFinalizeFunc val'
return val''
return result
setTypeInfoBaseFinalize :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_BaseFinalizeFunc -> m ()
setTypeInfoBaseFinalize s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: FunPtr GObject.Callbacks.C_BaseFinalizeFunc)
clearTypeInfoBaseFinalize :: MonadIO m => TypeInfo -> m ()
clearTypeInfoBaseFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_BaseFinalizeFunc)
#if ENABLE_OVERLOADING
data TypeInfoBaseFinalizeFieldInfo
instance AttrInfo TypeInfoBaseFinalizeFieldInfo where
type AttrAllowedOps TypeInfoBaseFinalizeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeInfoBaseFinalizeFieldInfo = (~) (FunPtr GObject.Callbacks.C_BaseFinalizeFunc)
type AttrBaseTypeConstraint TypeInfoBaseFinalizeFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoBaseFinalizeFieldInfo = Maybe GObject.Callbacks.BaseFinalizeFunc
type AttrLabel TypeInfoBaseFinalizeFieldInfo = "base_finalize"
type AttrOrigin TypeInfoBaseFinalizeFieldInfo = TypeInfo
attrGet _ = getTypeInfoBaseFinalize
attrSet _ = setTypeInfoBaseFinalize
attrConstruct = undefined
attrClear _ = clearTypeInfoBaseFinalize
typeInfo_baseFinalize :: AttrLabelProxy "baseFinalize"
typeInfo_baseFinalize = AttrLabelProxy
#endif
getTypeInfoClassInit :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.ClassInitFunc)
getTypeInfoClassInit s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO (FunPtr GObject.Callbacks.C_ClassInitFunc)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GObject.Callbacks.dynamic_ClassInitFunc val'
return val''
return result
setTypeInfoClassInit :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_ClassInitFunc -> m ()
setTypeInfoClassInit s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: FunPtr GObject.Callbacks.C_ClassInitFunc)
clearTypeInfoClassInit :: MonadIO m => TypeInfo -> m ()
clearTypeInfoClassInit s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_ClassInitFunc)
#if ENABLE_OVERLOADING
data TypeInfoClassInitFieldInfo
instance AttrInfo TypeInfoClassInitFieldInfo where
type AttrAllowedOps TypeInfoClassInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeInfoClassInitFieldInfo = (~) (FunPtr GObject.Callbacks.C_ClassInitFunc)
type AttrBaseTypeConstraint TypeInfoClassInitFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoClassInitFieldInfo = Maybe GObject.Callbacks.ClassInitFunc
type AttrLabel TypeInfoClassInitFieldInfo = "class_init"
type AttrOrigin TypeInfoClassInitFieldInfo = TypeInfo
attrGet _ = getTypeInfoClassInit
attrSet _ = setTypeInfoClassInit
attrConstruct = undefined
attrClear _ = clearTypeInfoClassInit
typeInfo_classInit :: AttrLabelProxy "classInit"
typeInfo_classInit = AttrLabelProxy
#endif
getTypeInfoClassFinalize :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.ClassFinalizeFunc)
getTypeInfoClassFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO (FunPtr GObject.Callbacks.C_ClassFinalizeFunc)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GObject.Callbacks.dynamic_ClassFinalizeFunc val'
return val''
return result
setTypeInfoClassFinalize :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_ClassFinalizeFunc -> m ()
setTypeInfoClassFinalize s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (val :: FunPtr GObject.Callbacks.C_ClassFinalizeFunc)
clearTypeInfoClassFinalize :: MonadIO m => TypeInfo -> m ()
clearTypeInfoClassFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_ClassFinalizeFunc)
#if ENABLE_OVERLOADING
data TypeInfoClassFinalizeFieldInfo
instance AttrInfo TypeInfoClassFinalizeFieldInfo where
type AttrAllowedOps TypeInfoClassFinalizeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeInfoClassFinalizeFieldInfo = (~) (FunPtr GObject.Callbacks.C_ClassFinalizeFunc)
type AttrBaseTypeConstraint TypeInfoClassFinalizeFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoClassFinalizeFieldInfo = Maybe GObject.Callbacks.ClassFinalizeFunc
type AttrLabel TypeInfoClassFinalizeFieldInfo = "class_finalize"
type AttrOrigin TypeInfoClassFinalizeFieldInfo = TypeInfo
attrGet _ = getTypeInfoClassFinalize
attrSet _ = setTypeInfoClassFinalize
attrConstruct = undefined
attrClear _ = clearTypeInfoClassFinalize
typeInfo_classFinalize :: AttrLabelProxy "classFinalize"
typeInfo_classFinalize = AttrLabelProxy
#endif
getTypeInfoClassData :: MonadIO m => TypeInfo -> m (Ptr ())
getTypeInfoClassData s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO (Ptr ())
return val
setTypeInfoClassData :: MonadIO m => TypeInfo -> Ptr () -> m ()
setTypeInfoClassData s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 40) (val :: Ptr ())
clearTypeInfoClassData :: MonadIO m => TypeInfo -> m ()
clearTypeInfoClassData s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 40) (FP.nullPtr :: Ptr ())
#if ENABLE_OVERLOADING
data TypeInfoClassDataFieldInfo
instance AttrInfo TypeInfoClassDataFieldInfo where
type AttrAllowedOps TypeInfoClassDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeInfoClassDataFieldInfo = (~) (Ptr ())
type AttrBaseTypeConstraint TypeInfoClassDataFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoClassDataFieldInfo = Ptr ()
type AttrLabel TypeInfoClassDataFieldInfo = "class_data"
type AttrOrigin TypeInfoClassDataFieldInfo = TypeInfo
attrGet _ = getTypeInfoClassData
attrSet _ = setTypeInfoClassData
attrConstruct = undefined
attrClear _ = clearTypeInfoClassData
typeInfo_classData :: AttrLabelProxy "classData"
typeInfo_classData = AttrLabelProxy
#endif
getTypeInfoInstanceSize :: MonadIO m => TypeInfo -> m Word16
getTypeInfoInstanceSize s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO Word16
return val
setTypeInfoInstanceSize :: MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoInstanceSize s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 48) (val :: Word16)
#if ENABLE_OVERLOADING
data TypeInfoInstanceSizeFieldInfo
instance AttrInfo TypeInfoInstanceSizeFieldInfo where
type AttrAllowedOps TypeInfoInstanceSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TypeInfoInstanceSizeFieldInfo = (~) Word16
type AttrBaseTypeConstraint TypeInfoInstanceSizeFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoInstanceSizeFieldInfo = Word16
type AttrLabel TypeInfoInstanceSizeFieldInfo = "instance_size"
type AttrOrigin TypeInfoInstanceSizeFieldInfo = TypeInfo
attrGet _ = getTypeInfoInstanceSize
attrSet _ = setTypeInfoInstanceSize
attrConstruct = undefined
attrClear _ = undefined
typeInfo_instanceSize :: AttrLabelProxy "instanceSize"
typeInfo_instanceSize = AttrLabelProxy
#endif
getTypeInfoNPreallocs :: MonadIO m => TypeInfo -> m Word16
getTypeInfoNPreallocs s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 50) :: IO Word16
return val
setTypeInfoNPreallocs :: MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoNPreallocs s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 50) (val :: Word16)
#if ENABLE_OVERLOADING
data TypeInfoNPreallocsFieldInfo
instance AttrInfo TypeInfoNPreallocsFieldInfo where
type AttrAllowedOps TypeInfoNPreallocsFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TypeInfoNPreallocsFieldInfo = (~) Word16
type AttrBaseTypeConstraint TypeInfoNPreallocsFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoNPreallocsFieldInfo = Word16
type AttrLabel TypeInfoNPreallocsFieldInfo = "n_preallocs"
type AttrOrigin TypeInfoNPreallocsFieldInfo = TypeInfo
attrGet _ = getTypeInfoNPreallocs
attrSet _ = setTypeInfoNPreallocs
attrConstruct = undefined
attrClear _ = undefined
typeInfo_nPreallocs :: AttrLabelProxy "nPreallocs"
typeInfo_nPreallocs = AttrLabelProxy
#endif
getTypeInfoInstanceInit :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.InstanceInitFunc)
getTypeInfoInstanceInit s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 56) :: IO (FunPtr GObject.Callbacks.C_InstanceInitFunc)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GObject.Callbacks.dynamic_InstanceInitFunc val'
return val''
return result
setTypeInfoInstanceInit :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_InstanceInitFunc -> m ()
setTypeInfoInstanceInit s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (val :: FunPtr GObject.Callbacks.C_InstanceInitFunc)
clearTypeInfoInstanceInit :: MonadIO m => TypeInfo -> m ()
clearTypeInfoInstanceInit s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_InstanceInitFunc)
#if ENABLE_OVERLOADING
data TypeInfoInstanceInitFieldInfo
instance AttrInfo TypeInfoInstanceInitFieldInfo where
type AttrAllowedOps TypeInfoInstanceInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeInfoInstanceInitFieldInfo = (~) (FunPtr GObject.Callbacks.C_InstanceInitFunc)
type AttrBaseTypeConstraint TypeInfoInstanceInitFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoInstanceInitFieldInfo = Maybe GObject.Callbacks.InstanceInitFunc
type AttrLabel TypeInfoInstanceInitFieldInfo = "instance_init"
type AttrOrigin TypeInfoInstanceInitFieldInfo = TypeInfo
attrGet _ = getTypeInfoInstanceInit
attrSet _ = setTypeInfoInstanceInit
attrConstruct = undefined
attrClear _ = clearTypeInfoInstanceInit
typeInfo_instanceInit :: AttrLabelProxy "instanceInit"
typeInfo_instanceInit = AttrLabelProxy
#endif
getTypeInfoValueTable :: MonadIO m => TypeInfo -> m (Maybe GObject.TypeValueTable.TypeValueTable)
getTypeInfoValueTable s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO (Ptr GObject.TypeValueTable.TypeValueTable)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newPtr GObject.TypeValueTable.TypeValueTable) val'
return val''
return result
setTypeInfoValueTable :: MonadIO m => TypeInfo -> Ptr GObject.TypeValueTable.TypeValueTable -> m ()
setTypeInfoValueTable s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 64) (val :: Ptr GObject.TypeValueTable.TypeValueTable)
clearTypeInfoValueTable :: MonadIO m => TypeInfo -> m ()
clearTypeInfoValueTable s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 64) (FP.nullPtr :: Ptr GObject.TypeValueTable.TypeValueTable)
#if ENABLE_OVERLOADING
data TypeInfoValueTableFieldInfo
instance AttrInfo TypeInfoValueTableFieldInfo where
type AttrAllowedOps TypeInfoValueTableFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeInfoValueTableFieldInfo = (~) (Ptr GObject.TypeValueTable.TypeValueTable)
type AttrBaseTypeConstraint TypeInfoValueTableFieldInfo = (~) TypeInfo
type AttrGetType TypeInfoValueTableFieldInfo = Maybe GObject.TypeValueTable.TypeValueTable
type AttrLabel TypeInfoValueTableFieldInfo = "value_table"
type AttrOrigin TypeInfoValueTableFieldInfo = TypeInfo
attrGet _ = getTypeInfoValueTable
attrSet _ = setTypeInfoValueTable
attrConstruct = undefined
attrClear _ = clearTypeInfoValueTable
typeInfo_valueTable :: AttrLabelProxy "valueTable"
typeInfo_valueTable = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList TypeInfo
type instance O.AttributeList TypeInfo = TypeInfoAttributeList
type TypeInfoAttributeList = ('[ '("classSize", TypeInfoClassSizeFieldInfo), '("baseInit", TypeInfoBaseInitFieldInfo), '("baseFinalize", TypeInfoBaseFinalizeFieldInfo), '("classInit", TypeInfoClassInitFieldInfo), '("classFinalize", TypeInfoClassFinalizeFieldInfo), '("classData", TypeInfoClassDataFieldInfo), '("instanceSize", TypeInfoInstanceSizeFieldInfo), '("nPreallocs", TypeInfoNPreallocsFieldInfo), '("instanceInit", TypeInfoInstanceInitFieldInfo), '("valueTable", TypeInfoValueTableFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveTypeInfoMethod (t :: Symbol) (o :: *) :: * where
ResolveTypeInfoMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTypeInfoMethod t TypeInfo, O.MethodInfo info TypeInfo p) => O.IsLabelProxy t (TypeInfo -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTypeInfoMethod t TypeInfo, O.MethodInfo info TypeInfo p) => O.IsLabel t (TypeInfo -> 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
#endif