{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Cairo.Structs.Rectangle
(
Rectangle(..) ,
newZeroRectangle ,
#if defined(ENABLE_OVERLOADING)
ResolveRectangleMethod ,
#endif
getRectangleHeight ,
#if defined(ENABLE_OVERLOADING)
rectangle_height ,
#endif
setRectangleHeight ,
getRectangleWidth ,
#if defined(ENABLE_OVERLOADING)
rectangle_width ,
#endif
setRectangleWidth ,
getRectangleX ,
#if defined(ENABLE_OVERLOADING)
rectangle_x ,
#endif
setRectangleX ,
getRectangleY ,
#if defined(ENABLE_OVERLOADING)
rectangle_y ,
#endif
setRectangleY ,
) 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.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
newtype Rectangle = Rectangle (SP.ManagedPtr Rectangle)
deriving (Rectangle -> Rectangle -> Bool
(Rectangle -> Rectangle -> Bool)
-> (Rectangle -> Rectangle -> Bool) -> Eq Rectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rectangle -> Rectangle -> Bool
$c/= :: Rectangle -> Rectangle -> Bool
== :: Rectangle -> Rectangle -> Bool
$c== :: Rectangle -> Rectangle -> Bool
Eq)
instance SP.ManagedPtrNewtype Rectangle where
toManagedPtr :: Rectangle -> ManagedPtr Rectangle
toManagedPtr (Rectangle ManagedPtr Rectangle
p) = ManagedPtr Rectangle
p
foreign import ccall "cairo_gobject_rectangle_get_type" c_cairo_gobject_rectangle_get_type ::
IO GType
type instance O.ParentTypes Rectangle = '[]
instance O.HasParentTypes Rectangle
instance B.Types.TypedObject Rectangle where
glibType :: IO GType
glibType = IO GType
c_cairo_gobject_rectangle_get_type
instance B.Types.GBoxed Rectangle
instance B.GValue.IsGValue (Maybe Rectangle) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_cairo_gobject_rectangle_get_type
gvalueSet_ :: Ptr GValue -> Maybe Rectangle -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Rectangle
P.Nothing = Ptr GValue -> Ptr Rectangle -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Rectangle
forall a. Ptr a
FP.nullPtr :: FP.Ptr Rectangle)
gvalueSet_ Ptr GValue
gv (P.Just Rectangle
obj) = Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Rectangle
obj (Ptr GValue -> Ptr Rectangle -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Rectangle)
gvalueGet_ Ptr GValue
gv = do
Ptr Rectangle
ptr <- Ptr GValue -> IO (Ptr Rectangle)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Rectangle)
if Ptr Rectangle
ptr Ptr Rectangle -> Ptr Rectangle -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Rectangle
forall a. Ptr a
FP.nullPtr
then Rectangle -> Maybe Rectangle
forall a. a -> Maybe a
P.Just (Rectangle -> Maybe Rectangle)
-> IO Rectangle -> IO (Maybe Rectangle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Rectangle -> Rectangle
Rectangle Ptr Rectangle
ptr
else Maybe Rectangle -> IO (Maybe Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Rectangle
forall a. Maybe a
P.Nothing
newZeroRectangle :: MonadIO m => m Rectangle
newZeroRectangle :: forall (m :: * -> *). MonadIO m => m Rectangle
newZeroRectangle = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
32 IO (Ptr Rectangle)
-> (Ptr Rectangle -> IO Rectangle) -> IO Rectangle
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Rectangle
instance tag ~ 'AttrSet => Constructible Rectangle tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr Rectangle -> Rectangle)
-> [AttrOp Rectangle tag] -> m Rectangle
new ManagedPtr Rectangle -> Rectangle
_ [AttrOp Rectangle tag]
attrs = do
Rectangle
o <- m Rectangle
forall (m :: * -> *). MonadIO m => m Rectangle
newZeroRectangle
Rectangle -> [AttrOp Rectangle 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Rectangle
o [AttrOp Rectangle tag]
[AttrOp Rectangle 'AttrSet]
attrs
Rectangle -> m Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
o
getRectangleX :: MonadIO m => Rectangle -> m Double
getRectangleX :: forall (m :: * -> *). MonadIO m => Rectangle -> m Double
getRectangleX Rectangle
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Double) -> IO Double)
-> (Ptr Rectangle -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setRectangleX :: MonadIO m => Rectangle -> Double -> m ()
setRectangleX :: forall (m :: * -> *). MonadIO m => Rectangle -> Double -> m ()
setRectangleX Rectangle
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data RectangleXFieldInfo
instance AttrInfo RectangleXFieldInfo where
type AttrBaseTypeConstraint RectangleXFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleXFieldInfo = (~) Double
type AttrTransferTypeConstraint RectangleXFieldInfo = (~)Double
type AttrTransferType RectangleXFieldInfo = Double
type AttrGetType RectangleXFieldInfo = Double
type AttrLabel RectangleXFieldInfo = "x"
type AttrOrigin RectangleXFieldInfo = Rectangle
attrGet = getRectangleX
attrSet = setRectangleX
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Cairo.Structs.Rectangle.x"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-cairo-1.0.26/docs/GI-Cairo-Structs-Rectangle.html#g:attr:x"
})
rectangle_x :: AttrLabelProxy "x"
rectangle_x = AttrLabelProxy
#endif
getRectangleY :: MonadIO m => Rectangle -> m Double
getRectangleY :: forall (m :: * -> *). MonadIO m => Rectangle -> m Double
getRectangleY Rectangle
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Double) -> IO Double)
-> (Ptr Rectangle -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setRectangleY :: MonadIO m => Rectangle -> Double -> m ()
setRectangleY :: forall (m :: * -> *). MonadIO m => Rectangle -> Double -> m ()
setRectangleY Rectangle
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data RectangleYFieldInfo
instance AttrInfo RectangleYFieldInfo where
type AttrBaseTypeConstraint RectangleYFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleYFieldInfo = (~) Double
type AttrTransferTypeConstraint RectangleYFieldInfo = (~)Double
type AttrTransferType RectangleYFieldInfo = Double
type AttrGetType RectangleYFieldInfo = Double
type AttrLabel RectangleYFieldInfo = "y"
type AttrOrigin RectangleYFieldInfo = Rectangle
attrGet = getRectangleY
attrSet = setRectangleY
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Cairo.Structs.Rectangle.y"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-cairo-1.0.26/docs/GI-Cairo-Structs-Rectangle.html#g:attr:y"
})
rectangle_y :: AttrLabelProxy "y"
rectangle_y = AttrLabelProxy
#endif
getRectangleWidth :: MonadIO m => Rectangle -> m Double
getRectangleWidth :: forall (m :: * -> *). MonadIO m => Rectangle -> m Double
getRectangleWidth Rectangle
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Double) -> IO Double)
-> (Ptr Rectangle -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setRectangleWidth :: MonadIO m => Rectangle -> Double -> m ()
setRectangleWidth :: forall (m :: * -> *). MonadIO m => Rectangle -> Double -> m ()
setRectangleWidth Rectangle
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data RectangleWidthFieldInfo
instance AttrInfo RectangleWidthFieldInfo where
type AttrBaseTypeConstraint RectangleWidthFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleWidthFieldInfo = (~) Double
type AttrTransferTypeConstraint RectangleWidthFieldInfo = (~)Double
type AttrTransferType RectangleWidthFieldInfo = Double
type AttrGetType RectangleWidthFieldInfo = Double
type AttrLabel RectangleWidthFieldInfo = "width"
type AttrOrigin RectangleWidthFieldInfo = Rectangle
attrGet = getRectangleWidth
attrSet = setRectangleWidth
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Cairo.Structs.Rectangle.width"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-cairo-1.0.26/docs/GI-Cairo-Structs-Rectangle.html#g:attr:width"
})
rectangle_width :: AttrLabelProxy "width"
rectangle_width = AttrLabelProxy
#endif
getRectangleHeight :: MonadIO m => Rectangle -> m Double
getRectangleHeight :: forall (m :: * -> *). MonadIO m => Rectangle -> m Double
getRectangleHeight Rectangle
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Double) -> IO Double)
-> (Ptr Rectangle -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setRectangleHeight :: MonadIO m => Rectangle -> Double -> m ()
setRectangleHeight :: forall (m :: * -> *). MonadIO m => Rectangle -> Double -> m ()
setRectangleHeight Rectangle
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data RectangleHeightFieldInfo
instance AttrInfo RectangleHeightFieldInfo where
type AttrBaseTypeConstraint RectangleHeightFieldInfo = (~) Rectangle
type AttrAllowedOps RectangleHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RectangleHeightFieldInfo = (~) Double
type AttrTransferTypeConstraint RectangleHeightFieldInfo = (~)Double
type AttrTransferType RectangleHeightFieldInfo = Double
type AttrGetType RectangleHeightFieldInfo = Double
type AttrLabel RectangleHeightFieldInfo = "height"
type AttrOrigin RectangleHeightFieldInfo = Rectangle
attrGet = getRectangleHeight
attrSet = setRectangleHeight
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Cairo.Structs.Rectangle.height"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-cairo-1.0.26/docs/GI-Cairo-Structs-Rectangle.html#g:attr:height"
})
rectangle_height :: AttrLabelProxy "height"
rectangle_height = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Rectangle
type instance O.AttributeList Rectangle = RectangleAttributeList
type RectangleAttributeList = ('[ '("x", RectangleXFieldInfo), '("y", RectangleYFieldInfo), '("width", RectangleWidthFieldInfo), '("height", RectangleHeightFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveRectangleMethod (t :: Symbol) (o :: *) :: * where
ResolveRectangleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRectangleMethod t Rectangle, O.OverloadedMethod info Rectangle p) => OL.IsLabel t (Rectangle -> 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 ~ ResolveRectangleMethod t Rectangle, O.OverloadedMethod info Rectangle p, R.HasField t Rectangle p) => R.HasField t Rectangle p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveRectangleMethod t Rectangle, O.OverloadedMethodInfo info Rectangle) => OL.IsLabel t (O.MethodProxy info Rectangle) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif