{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- AtkAttribute is a string name\/value pair representing a generic
-- attribute. This can be used to expose additional information from
-- an accessible object as a whole (see 'GI.Atk.Objects.Object.objectGetAttributes')
-- or an document (see 'GI.Atk.Interfaces.Document.documentGetAttributes'). In the case of
-- text attributes (see 'GI.Atk.Interfaces.Text.textGetDefaultAttributes'),
-- t'GI.Atk.Enums.TextAttribute' enum defines all the possible text attribute
-- names. You can use 'GI.Atk.Functions.textAttributeGetName' to get the string
-- name from the enum value. See also 'GI.Atk.Functions.textAttributeForName'
-- and 'GI.Atk.Functions.textAttributeGetValue' for more information.
-- 
-- A string name\/value pair representing a generic attribute.

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

module GI.Atk.Structs.Attribute
    ( 

-- * Exported types
    Attribute(..)                           ,
    newZeroAttribute                        ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveAttributeMethod                  ,
#endif

-- ** setFree #method:setFree#

    attributeSetFree                        ,




 -- * Properties


-- ** name #attr:name#
-- | The attribute name.

#if defined(ENABLE_OVERLOADING)
    attribute_name                          ,
#endif
    clearAttributeName                      ,
    getAttributeName                        ,
    setAttributeName                        ,


-- ** value #attr:value#
-- | the value of the attribute, represented as a string.

#if defined(ENABLE_OVERLOADING)
    attribute_value                         ,
#endif
    clearAttributeValue                     ,
    getAttributeValue                       ,
    setAttributeValue                       ,




    ) 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.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 Attribute = Attribute (SP.ManagedPtr Attribute)
    deriving (Attribute -> Attribute -> Bool
(Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool) -> Eq Attribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attribute -> Attribute -> Bool
== :: Attribute -> Attribute -> Bool
$c/= :: Attribute -> Attribute -> Bool
/= :: Attribute -> Attribute -> Bool
Eq)

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

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


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

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


-- | Get the value of the “@name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' attribute #name
-- @
getAttributeName :: MonadIO m => Attribute -> m (Maybe T.Text)
getAttributeName :: forall (m :: * -> *). MonadIO m => Attribute -> m (Maybe Text)
getAttributeName Attribute
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Attribute -> (Ptr Attribute -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Attribute
s ((Ptr Attribute -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr Attribute -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr Attribute
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr Attribute
ptr Ptr Attribute -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

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

-- | Set the value of the “@name@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #name
-- @
clearAttributeName :: MonadIO m => Attribute -> m ()
clearAttributeName :: forall (m :: * -> *). MonadIO m => Attribute -> m ()
clearAttributeName Attribute
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Attribute -> (Ptr Attribute -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Attribute
s ((Ptr Attribute -> IO ()) -> IO ())
-> (Ptr Attribute -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Attribute
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Attribute
ptr Ptr Attribute -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data AttributeNameFieldInfo
instance AttrInfo AttributeNameFieldInfo where
    type AttrBaseTypeConstraint AttributeNameFieldInfo = (~) Attribute
    type AttrAllowedOps AttributeNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint AttributeNameFieldInfo = (~) CString
    type AttrTransferTypeConstraint AttributeNameFieldInfo = (~)CString
    type AttrTransferType AttributeNameFieldInfo = CString
    type AttrGetType AttributeNameFieldInfo = Maybe T.Text
    type AttrLabel AttributeNameFieldInfo = "name"
    type AttrOrigin AttributeNameFieldInfo = Attribute
    attrGet = getAttributeName
    attrSet = setAttributeName
    attrConstruct = undefined
    attrClear = clearAttributeName
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.Attribute.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.25/docs/GI-Atk-Structs-Attribute.html#g:attr:name"
        })

attribute_name :: AttrLabelProxy "name"
attribute_name = 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' attribute #value
-- @
getAttributeValue :: MonadIO m => Attribute -> m (Maybe T.Text)
getAttributeValue :: forall (m :: * -> *). MonadIO m => Attribute -> m (Maybe Text)
getAttributeValue Attribute
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Attribute -> (Ptr Attribute -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Attribute
s ((Ptr Attribute -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr Attribute -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr Attribute
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr Attribute
ptr Ptr Attribute -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | 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' attribute [ #value 'Data.GI.Base.Attributes.:=' value ]
-- @
setAttributeValue :: MonadIO m => Attribute -> CString -> m ()
setAttributeValue :: forall (m :: * -> *). MonadIO m => Attribute -> CString -> m ()
setAttributeValue Attribute
s CString
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Attribute -> (Ptr Attribute -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Attribute
s ((Ptr Attribute -> IO ()) -> IO ())
-> (Ptr Attribute -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Attribute
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Attribute
ptr Ptr Attribute -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)

-- | Set the value of the “@value@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #value
-- @
clearAttributeValue :: MonadIO m => Attribute -> m ()
clearAttributeValue :: forall (m :: * -> *). MonadIO m => Attribute -> m ()
clearAttributeValue Attribute
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Attribute -> (Ptr Attribute -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Attribute
s ((Ptr Attribute -> IO ()) -> IO ())
-> (Ptr Attribute -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Attribute
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Attribute
ptr Ptr Attribute -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data AttributeValueFieldInfo
instance AttrInfo AttributeValueFieldInfo where
    type AttrBaseTypeConstraint AttributeValueFieldInfo = (~) Attribute
    type AttrAllowedOps AttributeValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint AttributeValueFieldInfo = (~) CString
    type AttrTransferTypeConstraint AttributeValueFieldInfo = (~)CString
    type AttrTransferType AttributeValueFieldInfo = CString
    type AttrGetType AttributeValueFieldInfo = Maybe T.Text
    type AttrLabel AttributeValueFieldInfo = "value"
    type AttrOrigin AttributeValueFieldInfo = Attribute
    attrGet = getAttributeValue
    attrSet = setAttributeValue
    attrConstruct = undefined
    attrClear = clearAttributeValue
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.Attribute.value"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.25/docs/GI-Atk-Structs-Attribute.html#g:attr:value"
        })

attribute_value :: AttrLabelProxy "value"
attribute_value = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Attribute
type instance O.AttributeList Attribute = AttributeAttributeList
type AttributeAttributeList = ('[ '("name", AttributeNameFieldInfo), '("value", AttributeValueFieldInfo)] :: [(Symbol, *)])
#endif

-- method Attribute::set_free
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "attrib_set"
--           , argType = TGSList (TBasicType TPtr)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #AtkAttributeSet to free"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_attribute_set_free" atk_attribute_set_free :: 
    Ptr (GSList (Ptr ())) ->                -- attrib_set : TGSList (TBasicType TPtr)
    IO ()

-- | Frees the memory used by an @/AtkAttributeSet/@, including all its
-- @/AtkAttributes/@.
attributeSetFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Ptr ()]
    -- ^ /@attribSet@/: The @/AtkAttributeSet/@ to free
    -> m ()
attributeSetFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => [Ptr ()] -> m ()
attributeSetFree [Ptr ()]
attribSet = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GSList (Ptr ()))
attribSet' <- [Ptr ()] -> IO (Ptr (GSList (Ptr ())))
forall a. [Ptr a] -> IO (Ptr (GSList (Ptr a)))
packGSList [Ptr ()]
attribSet
    Ptr (GSList (Ptr ())) -> IO ()
atk_attribute_set_free Ptr (GSList (Ptr ()))
attribSet'
    Ptr (GSList (Ptr ())) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr ()))
attribSet'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAttributeMethod (t :: Symbol) (o :: *) :: * where
    ResolveAttributeMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif