{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gsk.Structs.Stroke
(
Stroke(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveStrokeMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
StrokeCopyMethodInfo ,
#endif
strokeCopy ,
strokeEqual ,
#if defined(ENABLE_OVERLOADING)
StrokeFreeMethodInfo ,
#endif
strokeFree ,
#if defined(ENABLE_OVERLOADING)
StrokeGetDashMethodInfo ,
#endif
strokeGetDash ,
#if defined(ENABLE_OVERLOADING)
StrokeGetDashOffsetMethodInfo ,
#endif
strokeGetDashOffset ,
#if defined(ENABLE_OVERLOADING)
StrokeGetLineCapMethodInfo ,
#endif
strokeGetLineCap ,
#if defined(ENABLE_OVERLOADING)
StrokeGetLineJoinMethodInfo ,
#endif
strokeGetLineJoin ,
#if defined(ENABLE_OVERLOADING)
StrokeGetLineWidthMethodInfo ,
#endif
strokeGetLineWidth ,
#if defined(ENABLE_OVERLOADING)
StrokeGetMiterLimitMethodInfo ,
#endif
strokeGetMiterLimit ,
strokeNew ,
#if defined(ENABLE_OVERLOADING)
StrokeSetDashMethodInfo ,
#endif
strokeSetDash ,
#if defined(ENABLE_OVERLOADING)
StrokeSetDashOffsetMethodInfo ,
#endif
strokeSetDashOffset ,
#if defined(ENABLE_OVERLOADING)
StrokeSetLineCapMethodInfo ,
#endif
strokeSetLineCap ,
#if defined(ENABLE_OVERLOADING)
StrokeSetLineJoinMethodInfo ,
#endif
strokeSetLineJoin ,
#if defined(ENABLE_OVERLOADING)
StrokeSetLineWidthMethodInfo ,
#endif
strokeSetLineWidth ,
#if defined(ENABLE_OVERLOADING)
StrokeSetMiterLimitMethodInfo ,
#endif
strokeSetMiterLimit ,
#if defined(ENABLE_OVERLOADING)
StrokeToCairoMethodInfo ,
#endif
strokeToCairo ,
) 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.Kind as DK
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
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
#else
import qualified GI.Cairo.Structs.Context as Cairo.Context
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
#endif
newtype Stroke = Stroke (SP.ManagedPtr Stroke)
deriving (Stroke -> Stroke -> Bool
(Stroke -> Stroke -> Bool)
-> (Stroke -> Stroke -> Bool) -> Eq Stroke
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Stroke -> Stroke -> Bool
== :: Stroke -> Stroke -> Bool
$c/= :: Stroke -> Stroke -> Bool
/= :: Stroke -> Stroke -> Bool
Eq)
instance SP.ManagedPtrNewtype Stroke where
toManagedPtr :: Stroke -> ManagedPtr Stroke
toManagedPtr (Stroke ManagedPtr Stroke
p) = ManagedPtr Stroke
p
foreign import ccall "gsk_stroke_get_type" c_gsk_stroke_get_type ::
IO GType
type instance O.ParentTypes Stroke = '[]
instance O.HasParentTypes Stroke
instance B.Types.TypedObject Stroke where
glibType :: IO GType
glibType = IO GType
c_gsk_stroke_get_type
instance B.Types.GBoxed Stroke
instance B.GValue.IsGValue (Maybe Stroke) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gsk_stroke_get_type
gvalueSet_ :: Ptr GValue -> Maybe Stroke -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Stroke
P.Nothing = Ptr GValue -> Ptr Stroke -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Stroke
forall a. Ptr a
FP.nullPtr :: FP.Ptr Stroke)
gvalueSet_ Ptr GValue
gv (P.Just Stroke
obj) = Stroke -> (Ptr Stroke -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Stroke
obj (Ptr GValue -> Ptr Stroke -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Stroke)
gvalueGet_ Ptr GValue
gv = do
Ptr Stroke
ptr <- Ptr GValue -> IO (Ptr Stroke)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Stroke)
if Ptr Stroke
ptr Ptr Stroke -> Ptr Stroke -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Stroke
forall a. Ptr a
FP.nullPtr
then Stroke -> Maybe Stroke
forall a. a -> Maybe a
P.Just (Stroke -> Maybe Stroke) -> IO Stroke -> IO (Maybe Stroke)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Stroke -> Stroke) -> Ptr Stroke -> IO Stroke
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Stroke -> Stroke
Stroke Ptr Stroke
ptr
else Maybe Stroke -> IO (Maybe Stroke)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Stroke
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Stroke
type instance O.AttributeList Stroke = StrokeAttributeList
type StrokeAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gsk_stroke_new" gsk_stroke_new ::
CFloat ->
IO (Ptr Stroke)
strokeNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Float
-> m Stroke
strokeNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Float -> m Stroke
strokeNew Float
lineWidth = IO Stroke -> m Stroke
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Stroke -> m Stroke) -> IO Stroke -> m Stroke
forall a b. (a -> b) -> a -> b
$ do
let lineWidth' :: CFloat
lineWidth' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
lineWidth
Ptr Stroke
result <- CFloat -> IO (Ptr Stroke)
gsk_stroke_new CFloat
lineWidth'
Text -> Ptr Stroke -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"strokeNew" Ptr Stroke
result
Stroke
result' <- ((ManagedPtr Stroke -> Stroke) -> Ptr Stroke -> IO Stroke
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Stroke -> Stroke
Stroke) Ptr Stroke
result
Stroke -> IO Stroke
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Stroke
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gsk_stroke_copy" gsk_stroke_copy ::
Ptr Stroke ->
IO (Ptr Stroke)
strokeCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m Stroke
strokeCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> m Stroke
strokeCopy Stroke
other = IO Stroke -> m Stroke
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Stroke -> m Stroke) -> IO Stroke -> m Stroke
forall a b. (a -> b) -> a -> b
$ do
Ptr Stroke
other' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
other
Ptr Stroke
result <- Ptr Stroke -> IO (Ptr Stroke)
gsk_stroke_copy Ptr Stroke
other'
Text -> Ptr Stroke -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"strokeCopy" Ptr Stroke
result
Stroke
result' <- ((ManagedPtr Stroke -> Stroke) -> Ptr Stroke -> IO Stroke
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Stroke -> Stroke
Stroke) Ptr Stroke
result
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
other
Stroke -> IO Stroke
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Stroke
result'
#if defined(ENABLE_OVERLOADING)
data StrokeCopyMethodInfo
instance (signature ~ (m Stroke), MonadIO m) => O.OverloadedMethod StrokeCopyMethodInfo Stroke signature where
overloadedMethod = strokeCopy
instance O.OverloadedMethodInfo StrokeCopyMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeCopy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeCopy"
})
#endif
foreign import ccall "gsk_stroke_free" gsk_stroke_free ::
Ptr Stroke ->
IO ()
strokeFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m ()
strokeFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Stroke -> m ()
strokeFree Stroke
self = 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 Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
Ptr Stroke -> IO ()
gsk_stroke_free Ptr Stroke
self'
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod StrokeFreeMethodInfo Stroke signature where
overloadedMethod = strokeFree
instance O.OverloadedMethodInfo StrokeFreeMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeFree",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeFree"
})
#endif
foreign import ccall "gsk_stroke_get_dash" gsk_stroke_get_dash ::
Ptr Stroke ->
Ptr FCT.CSize ->
IO (Ptr CFloat)
strokeGetDash ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m (Maybe [Float])
strokeGetDash :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> m (Maybe [Float])
strokeGetDash Stroke
self = IO (Maybe [Float]) -> m (Maybe [Float])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Float]) -> m (Maybe [Float]))
-> IO (Maybe [Float]) -> m (Maybe [Float])
forall a b. (a -> b) -> a -> b
$ do
Ptr Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
Ptr CSize
nDash <- IO (Ptr CSize)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr FCT.CSize)
Ptr CFloat
result <- Ptr Stroke -> Ptr CSize -> IO (Ptr CFloat)
gsk_stroke_get_dash Ptr Stroke
self' Ptr CSize
nDash
CSize
nDash' <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
nDash
Maybe [Float]
maybeResult <- Ptr CFloat -> (Ptr CFloat -> IO [Float]) -> IO (Maybe [Float])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CFloat
result ((Ptr CFloat -> IO [Float]) -> IO (Maybe [Float]))
-> (Ptr CFloat -> IO [Float]) -> IO (Maybe [Float])
forall a b. (a -> b) -> a -> b
$ \Ptr CFloat
result' -> do
[Float]
result'' <- ((CFloat -> Float) -> CSize -> Ptr CFloat -> IO [Float]
forall a b c.
(Integral a, Storable b) =>
(b -> c) -> a -> Ptr b -> IO [c]
unpackMapStorableArrayWithLength CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CSize
nDash') Ptr CFloat
result'
[Float] -> IO [Float]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Float]
result''
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
nDash
Maybe [Float] -> IO (Maybe [Float])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Float]
maybeResult
#if defined(ENABLE_OVERLOADING)
data StrokeGetDashMethodInfo
instance (signature ~ (m (Maybe [Float])), MonadIO m) => O.OverloadedMethod StrokeGetDashMethodInfo Stroke signature where
overloadedMethod = strokeGetDash
instance O.OverloadedMethodInfo StrokeGetDashMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeGetDash",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeGetDash"
})
#endif
foreign import ccall "gsk_stroke_get_dash_offset" gsk_stroke_get_dash_offset ::
Ptr Stroke ->
IO CFloat
strokeGetDashOffset ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m Float
strokeGetDashOffset :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> m Float
strokeGetDashOffset Stroke
self = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
Ptr Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
CFloat
result <- Ptr Stroke -> IO CFloat
gsk_stroke_get_dash_offset Ptr Stroke
self'
let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'
#if defined(ENABLE_OVERLOADING)
data StrokeGetDashOffsetMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod StrokeGetDashOffsetMethodInfo Stroke signature where
overloadedMethod = strokeGetDashOffset
instance O.OverloadedMethodInfo StrokeGetDashOffsetMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeGetDashOffset",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeGetDashOffset"
})
#endif
foreign import ccall "gsk_stroke_get_line_cap" gsk_stroke_get_line_cap ::
Ptr Stroke ->
IO CUInt
strokeGetLineCap ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m Gsk.Enums.LineCap
strokeGetLineCap :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> m LineCap
strokeGetLineCap Stroke
self = IO LineCap -> m LineCap
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LineCap -> m LineCap) -> IO LineCap -> m LineCap
forall a b. (a -> b) -> a -> b
$ do
Ptr Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
CUInt
result <- Ptr Stroke -> IO CUInt
gsk_stroke_get_line_cap Ptr Stroke
self'
let result' :: LineCap
result' = (Int -> LineCap
forall a. Enum a => Int -> a
toEnum (Int -> LineCap) -> (CUInt -> Int) -> CUInt -> LineCap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
LineCap -> IO LineCap
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LineCap
result'
#if defined(ENABLE_OVERLOADING)
data StrokeGetLineCapMethodInfo
instance (signature ~ (m Gsk.Enums.LineCap), MonadIO m) => O.OverloadedMethod StrokeGetLineCapMethodInfo Stroke signature where
overloadedMethod = strokeGetLineCap
instance O.OverloadedMethodInfo StrokeGetLineCapMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeGetLineCap",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeGetLineCap"
})
#endif
foreign import ccall "gsk_stroke_get_line_join" gsk_stroke_get_line_join ::
Ptr Stroke ->
IO CUInt
strokeGetLineJoin ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m Gsk.Enums.LineJoin
strokeGetLineJoin :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> m LineJoin
strokeGetLineJoin Stroke
self = IO LineJoin -> m LineJoin
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LineJoin -> m LineJoin) -> IO LineJoin -> m LineJoin
forall a b. (a -> b) -> a -> b
$ do
Ptr Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
CUInt
result <- Ptr Stroke -> IO CUInt
gsk_stroke_get_line_join Ptr Stroke
self'
let result' :: LineJoin
result' = (Int -> LineJoin
forall a. Enum a => Int -> a
toEnum (Int -> LineJoin) -> (CUInt -> Int) -> CUInt -> LineJoin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
LineJoin -> IO LineJoin
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LineJoin
result'
#if defined(ENABLE_OVERLOADING)
data StrokeGetLineJoinMethodInfo
instance (signature ~ (m Gsk.Enums.LineJoin), MonadIO m) => O.OverloadedMethod StrokeGetLineJoinMethodInfo Stroke signature where
overloadedMethod = strokeGetLineJoin
instance O.OverloadedMethodInfo StrokeGetLineJoinMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeGetLineJoin",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeGetLineJoin"
})
#endif
foreign import ccall "gsk_stroke_get_line_width" gsk_stroke_get_line_width ::
Ptr Stroke ->
IO CFloat
strokeGetLineWidth ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m Float
strokeGetLineWidth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> m Float
strokeGetLineWidth Stroke
self = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
Ptr Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
CFloat
result <- Ptr Stroke -> IO CFloat
gsk_stroke_get_line_width Ptr Stroke
self'
let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'
#if defined(ENABLE_OVERLOADING)
data StrokeGetLineWidthMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod StrokeGetLineWidthMethodInfo Stroke signature where
overloadedMethod = strokeGetLineWidth
instance O.OverloadedMethodInfo StrokeGetLineWidthMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeGetLineWidth",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeGetLineWidth"
})
#endif
foreign import ccall "gsk_stroke_get_miter_limit" gsk_stroke_get_miter_limit ::
Ptr Stroke ->
IO CFloat
strokeGetMiterLimit ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> m Float
strokeGetMiterLimit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> m Float
strokeGetMiterLimit Stroke
self = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
Ptr Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
CFloat
result <- Ptr Stroke -> IO CFloat
gsk_stroke_get_miter_limit Ptr Stroke
self'
let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'
#if defined(ENABLE_OVERLOADING)
data StrokeGetMiterLimitMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.OverloadedMethod StrokeGetMiterLimitMethodInfo Stroke signature where
overloadedMethod = strokeGetMiterLimit
instance O.OverloadedMethodInfo StrokeGetMiterLimitMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeGetMiterLimit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeGetMiterLimit"
})
#endif
foreign import ccall "gsk_stroke_set_dash" gsk_stroke_set_dash ::
Ptr Stroke ->
Ptr CFloat ->
FCT.CSize ->
IO ()
strokeSetDash ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> Maybe ([Float])
-> m ()
strokeSetDash :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> Maybe [Float] -> m ()
strokeSetDash Stroke
self Maybe [Float]
dash = 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
let nDash :: CSize
nDash = case Maybe [Float]
dash of
Maybe [Float]
Nothing -> CSize
0
Just [Float]
jDash -> Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ [Float] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Float]
jDash
Ptr Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
Ptr CFloat
maybeDash <- case Maybe [Float]
dash of
Maybe [Float]
Nothing -> Ptr CFloat -> IO (Ptr CFloat)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CFloat
forall a. Ptr a
nullPtr
Just [Float]
jDash -> do
Ptr CFloat
jDash' <- ((Float -> CFloat) -> [Float] -> IO (Ptr CFloat)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac) [Float]
jDash
Ptr CFloat -> IO (Ptr CFloat)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CFloat
jDash'
Ptr Stroke -> Ptr CFloat -> CSize -> IO ()
gsk_stroke_set_dash Ptr Stroke
self' Ptr CFloat
maybeDash CSize
nDash
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
maybeDash
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeSetDashMethodInfo
instance (signature ~ (Maybe ([Float]) -> m ()), MonadIO m) => O.OverloadedMethod StrokeSetDashMethodInfo Stroke signature where
overloadedMethod = strokeSetDash
instance O.OverloadedMethodInfo StrokeSetDashMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeSetDash",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeSetDash"
})
#endif
foreign import ccall "gsk_stroke_set_dash_offset" gsk_stroke_set_dash_offset ::
Ptr Stroke ->
CFloat ->
IO ()
strokeSetDashOffset ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> Float
-> m ()
strokeSetDashOffset :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> Float -> m ()
strokeSetDashOffset Stroke
self Float
offset = 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 Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
let offset' :: CFloat
offset' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
offset
Ptr Stroke -> CFloat -> IO ()
gsk_stroke_set_dash_offset Ptr Stroke
self' CFloat
offset'
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeSetDashOffsetMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod StrokeSetDashOffsetMethodInfo Stroke signature where
overloadedMethod = strokeSetDashOffset
instance O.OverloadedMethodInfo StrokeSetDashOffsetMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeSetDashOffset",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeSetDashOffset"
})
#endif
foreign import ccall "gsk_stroke_set_line_cap" gsk_stroke_set_line_cap ::
Ptr Stroke ->
CUInt ->
IO ()
strokeSetLineCap ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> Gsk.Enums.LineCap
-> m ()
strokeSetLineCap :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> LineCap -> m ()
strokeSetLineCap Stroke
self LineCap
lineCap = 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 Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
let lineCap' :: CUInt
lineCap' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (LineCap -> Int) -> LineCap -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LineCap -> Int
forall a. Enum a => a -> Int
fromEnum) LineCap
lineCap
Ptr Stroke -> CUInt -> IO ()
gsk_stroke_set_line_cap Ptr Stroke
self' CUInt
lineCap'
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeSetLineCapMethodInfo
instance (signature ~ (Gsk.Enums.LineCap -> m ()), MonadIO m) => O.OverloadedMethod StrokeSetLineCapMethodInfo Stroke signature where
overloadedMethod = strokeSetLineCap
instance O.OverloadedMethodInfo StrokeSetLineCapMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeSetLineCap",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeSetLineCap"
})
#endif
foreign import ccall "gsk_stroke_set_line_join" gsk_stroke_set_line_join ::
Ptr Stroke ->
CUInt ->
IO ()
strokeSetLineJoin ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> Gsk.Enums.LineJoin
-> m ()
strokeSetLineJoin :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> LineJoin -> m ()
strokeSetLineJoin Stroke
self LineJoin
lineJoin = 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 Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
let lineJoin' :: CUInt
lineJoin' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (LineJoin -> Int) -> LineJoin -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LineJoin -> Int
forall a. Enum a => a -> Int
fromEnum) LineJoin
lineJoin
Ptr Stroke -> CUInt -> IO ()
gsk_stroke_set_line_join Ptr Stroke
self' CUInt
lineJoin'
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeSetLineJoinMethodInfo
instance (signature ~ (Gsk.Enums.LineJoin -> m ()), MonadIO m) => O.OverloadedMethod StrokeSetLineJoinMethodInfo Stroke signature where
overloadedMethod = strokeSetLineJoin
instance O.OverloadedMethodInfo StrokeSetLineJoinMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeSetLineJoin",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeSetLineJoin"
})
#endif
foreign import ccall "gsk_stroke_set_line_width" gsk_stroke_set_line_width ::
Ptr Stroke ->
CFloat ->
IO ()
strokeSetLineWidth ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> Float
-> m ()
strokeSetLineWidth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> Float -> m ()
strokeSetLineWidth Stroke
self Float
lineWidth = 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 Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
let lineWidth' :: CFloat
lineWidth' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
lineWidth
Ptr Stroke -> CFloat -> IO ()
gsk_stroke_set_line_width Ptr Stroke
self' CFloat
lineWidth'
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeSetLineWidthMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod StrokeSetLineWidthMethodInfo Stroke signature where
overloadedMethod = strokeSetLineWidth
instance O.OverloadedMethodInfo StrokeSetLineWidthMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeSetLineWidth",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeSetLineWidth"
})
#endif
foreign import ccall "gsk_stroke_set_miter_limit" gsk_stroke_set_miter_limit ::
Ptr Stroke ->
CFloat ->
IO ()
strokeSetMiterLimit ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> Float
-> m ()
strokeSetMiterLimit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> Float -> m ()
strokeSetMiterLimit Stroke
self Float
limit = 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 Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
let limit' :: CFloat
limit' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
limit
Ptr Stroke -> CFloat -> IO ()
gsk_stroke_set_miter_limit Ptr Stroke
self' CFloat
limit'
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeSetMiterLimitMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.OverloadedMethod StrokeSetMiterLimitMethodInfo Stroke signature where
overloadedMethod = strokeSetMiterLimit
instance O.OverloadedMethodInfo StrokeSetMiterLimitMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeSetMiterLimit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeSetMiterLimit"
})
#endif
foreign import ccall "gsk_stroke_to_cairo" gsk_stroke_to_cairo ::
Ptr Stroke ->
Ptr Cairo.Context.Context ->
IO ()
strokeToCairo ::
(B.CallStack.HasCallStack, MonadIO m) =>
Stroke
-> Cairo.Context.Context
-> m ()
strokeToCairo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Stroke -> Context -> m ()
strokeToCairo Stroke
self Context
cr = 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 Stroke
self' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
self
Ptr Context
cr' <- Context -> IO (Ptr Context)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Context
cr
Ptr Stroke -> Ptr Context -> IO ()
gsk_stroke_to_cairo Ptr Stroke
self' Ptr Context
cr'
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
self
Context -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Context
cr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StrokeToCairoMethodInfo
instance (signature ~ (Cairo.Context.Context -> m ()), MonadIO m) => O.OverloadedMethod StrokeToCairoMethodInfo Stroke signature where
overloadedMethod = strokeToCairo
instance O.OverloadedMethodInfo StrokeToCairoMethodInfo Stroke where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Structs.Stroke.strokeToCairo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Structs-Stroke.html#v:strokeToCairo"
})
#endif
foreign import ccall "gsk_stroke_equal" gsk_stroke_equal ::
Ptr () ->
Ptr () ->
IO CInt
strokeEqual ::
(B.CallStack.HasCallStack, MonadIO m) =>
Ptr ()
-> Ptr ()
-> m Bool
strokeEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Ptr () -> Ptr () -> m Bool
strokeEqual Ptr ()
stroke1 Ptr ()
stroke2 = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
CInt
result <- Ptr () -> Ptr () -> IO CInt
gsk_stroke_equal Ptr ()
stroke1 Ptr ()
stroke2
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveStrokeMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveStrokeMethod "copy" o = StrokeCopyMethodInfo
ResolveStrokeMethod "free" o = StrokeFreeMethodInfo
ResolveStrokeMethod "toCairo" o = StrokeToCairoMethodInfo
ResolveStrokeMethod "getDash" o = StrokeGetDashMethodInfo
ResolveStrokeMethod "getDashOffset" o = StrokeGetDashOffsetMethodInfo
ResolveStrokeMethod "getLineCap" o = StrokeGetLineCapMethodInfo
ResolveStrokeMethod "getLineJoin" o = StrokeGetLineJoinMethodInfo
ResolveStrokeMethod "getLineWidth" o = StrokeGetLineWidthMethodInfo
ResolveStrokeMethod "getMiterLimit" o = StrokeGetMiterLimitMethodInfo
ResolveStrokeMethod "setDash" o = StrokeSetDashMethodInfo
ResolveStrokeMethod "setDashOffset" o = StrokeSetDashOffsetMethodInfo
ResolveStrokeMethod "setLineCap" o = StrokeSetLineCapMethodInfo
ResolveStrokeMethod "setLineJoin" o = StrokeSetLineJoinMethodInfo
ResolveStrokeMethod "setLineWidth" o = StrokeSetLineWidthMethodInfo
ResolveStrokeMethod "setMiterLimit" o = StrokeSetMiterLimitMethodInfo
ResolveStrokeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveStrokeMethod t Stroke, O.OverloadedMethod info Stroke p) => OL.IsLabel t (Stroke -> 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 ~ ResolveStrokeMethod t Stroke, O.OverloadedMethod info Stroke p, R.HasField t Stroke p) => R.HasField t Stroke p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveStrokeMethod t Stroke, O.OverloadedMethodInfo info Stroke) => OL.IsLabel t (O.MethodProxy info Stroke) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif