{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.GtkSource.Objects.StyleScheme
    ( 

-- * Exported types
    StyleScheme(..)                         ,
    IsStyleScheme                           ,
    toStyleScheme                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAuthors]("GI.GtkSource.Objects.StyleScheme#g:method:getAuthors"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDescription]("GI.GtkSource.Objects.StyleScheme#g:method:getDescription"), [getFilename]("GI.GtkSource.Objects.StyleScheme#g:method:getFilename"), [getId]("GI.GtkSource.Objects.StyleScheme#g:method:getId"), [getName]("GI.GtkSource.Objects.StyleScheme#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStyle]("GI.GtkSource.Objects.StyleScheme#g:method:getStyle").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveStyleSchemeMethod                ,
#endif

-- ** getAuthors #method:getAuthors#

#if defined(ENABLE_OVERLOADING)
    StyleSchemeGetAuthorsMethodInfo         ,
#endif
    styleSchemeGetAuthors                   ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    StyleSchemeGetDescriptionMethodInfo     ,
#endif
    styleSchemeGetDescription               ,


-- ** getFilename #method:getFilename#

#if defined(ENABLE_OVERLOADING)
    StyleSchemeGetFilenameMethodInfo        ,
#endif
    styleSchemeGetFilename                  ,


-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    StyleSchemeGetIdMethodInfo              ,
#endif
    styleSchemeGetId                        ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    StyleSchemeGetNameMethodInfo            ,
#endif
    styleSchemeGetName                      ,


-- ** getStyle #method:getStyle#

#if defined(ENABLE_OVERLOADING)
    StyleSchemeGetStyleMethodInfo           ,
#endif
    styleSchemeGetStyle                     ,




 -- * Properties


-- ** description #attr:description#
-- | Style scheme description, a translatable string to present to the user.

#if defined(ENABLE_OVERLOADING)
    StyleSchemeDescriptionPropertyInfo      ,
#endif
    getStyleSchemeDescription               ,
#if defined(ENABLE_OVERLOADING)
    styleSchemeDescription                  ,
#endif


-- ** filename #attr:filename#
-- | Style scheme filename or 'P.Nothing'.

#if defined(ENABLE_OVERLOADING)
    StyleSchemeFilenamePropertyInfo         ,
#endif
    getStyleSchemeFilename                  ,
#if defined(ENABLE_OVERLOADING)
    styleSchemeFilename                     ,
#endif


-- ** id #attr:id#
-- | Style scheme id, a unique string used to identify the style scheme
-- in t'GI.GtkSource.Objects.StyleSchemeManager.StyleSchemeManager'.

#if defined(ENABLE_OVERLOADING)
    StyleSchemeIdPropertyInfo               ,
#endif
    constructStyleSchemeId                  ,
    getStyleSchemeId                        ,
#if defined(ENABLE_OVERLOADING)
    styleSchemeId                           ,
#endif


-- ** name #attr:name#
-- | Style scheme name, a translatable string to present to the user.

#if defined(ENABLE_OVERLOADING)
    StyleSchemeNamePropertyInfo             ,
#endif
    getStyleSchemeName                      ,
#if defined(ENABLE_OVERLOADING)
    styleSchemeName                         ,
#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.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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.GtkSource.Objects.Style as GtkSource.Style

-- | Memory-managed wrapper type.
newtype StyleScheme = StyleScheme (SP.ManagedPtr StyleScheme)
    deriving (StyleScheme -> StyleScheme -> Bool
(StyleScheme -> StyleScheme -> Bool)
-> (StyleScheme -> StyleScheme -> Bool) -> Eq StyleScheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StyleScheme -> StyleScheme -> Bool
== :: StyleScheme -> StyleScheme -> Bool
$c/= :: StyleScheme -> StyleScheme -> Bool
/= :: StyleScheme -> StyleScheme -> Bool
Eq)

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

foreign import ccall "gtk_source_style_scheme_get_type"
    c_gtk_source_style_scheme_get_type :: IO B.Types.GType

instance B.Types.TypedObject StyleScheme where
    glibType :: IO GType
glibType = IO GType
c_gtk_source_style_scheme_get_type

instance B.Types.GObject StyleScheme

-- | Type class for types which can be safely cast to `StyleScheme`, for instance with `toStyleScheme`.
class (SP.GObject o, O.IsDescendantOf StyleScheme o) => IsStyleScheme o
instance (SP.GObject o, O.IsDescendantOf StyleScheme o) => IsStyleScheme o

instance O.HasParentTypes StyleScheme
type instance O.ParentTypes StyleScheme = '[GObject.Object.Object]

-- | Cast to `StyleScheme`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toStyleScheme :: (MIO.MonadIO m, IsStyleScheme o) => o -> m StyleScheme
toStyleScheme :: forall (m :: * -> *) o.
(MonadIO m, IsStyleScheme o) =>
o -> m StyleScheme
toStyleScheme = IO StyleScheme -> m StyleScheme
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO StyleScheme -> m StyleScheme)
-> (o -> IO StyleScheme) -> o -> m StyleScheme
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr StyleScheme -> StyleScheme) -> o -> IO StyleScheme
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr StyleScheme -> StyleScheme
StyleScheme

-- | Convert 'StyleScheme' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe StyleScheme) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_source_style_scheme_get_type
    gvalueSet_ :: Ptr GValue -> Maybe StyleScheme -> IO ()
gvalueSet_ Ptr GValue
gv Maybe StyleScheme
P.Nothing = Ptr GValue -> Ptr StyleScheme -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr StyleScheme
forall a. Ptr a
FP.nullPtr :: FP.Ptr StyleScheme)
    gvalueSet_ Ptr GValue
gv (P.Just StyleScheme
obj) = StyleScheme -> (Ptr StyleScheme -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StyleScheme
obj (Ptr GValue -> Ptr StyleScheme -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe StyleScheme)
gvalueGet_ Ptr GValue
gv = do
        Ptr StyleScheme
ptr <- Ptr GValue -> IO (Ptr StyleScheme)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr StyleScheme)
        if Ptr StyleScheme
ptr Ptr StyleScheme -> Ptr StyleScheme -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr StyleScheme
forall a. Ptr a
FP.nullPtr
        then StyleScheme -> Maybe StyleScheme
forall a. a -> Maybe a
P.Just (StyleScheme -> Maybe StyleScheme)
-> IO StyleScheme -> IO (Maybe StyleScheme)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr StyleScheme -> StyleScheme)
-> Ptr StyleScheme -> IO StyleScheme
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr StyleScheme -> StyleScheme
StyleScheme Ptr StyleScheme
ptr
        else Maybe StyleScheme -> IO (Maybe StyleScheme)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StyleScheme
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveStyleSchemeMethod (t :: Symbol) (o :: *) :: * where
    ResolveStyleSchemeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStyleSchemeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStyleSchemeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStyleSchemeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStyleSchemeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStyleSchemeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStyleSchemeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStyleSchemeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStyleSchemeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStyleSchemeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStyleSchemeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStyleSchemeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStyleSchemeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStyleSchemeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStyleSchemeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStyleSchemeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStyleSchemeMethod "getAuthors" o = StyleSchemeGetAuthorsMethodInfo
    ResolveStyleSchemeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStyleSchemeMethod "getDescription" o = StyleSchemeGetDescriptionMethodInfo
    ResolveStyleSchemeMethod "getFilename" o = StyleSchemeGetFilenameMethodInfo
    ResolveStyleSchemeMethod "getId" o = StyleSchemeGetIdMethodInfo
    ResolveStyleSchemeMethod "getName" o = StyleSchemeGetNameMethodInfo
    ResolveStyleSchemeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveStyleSchemeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStyleSchemeMethod "getStyle" o = StyleSchemeGetStyleMethodInfo
    ResolveStyleSchemeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStyleSchemeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStyleSchemeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveStyleSchemeMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' styleScheme #description
-- @
getStyleSchemeDescription :: (MonadIO m, IsStyleScheme o) => o -> m (Maybe T.Text)
getStyleSchemeDescription :: forall (m :: * -> *) o.
(MonadIO m, IsStyleScheme o) =>
o -> m (Maybe Text)
getStyleSchemeDescription o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"description"

#if defined(ENABLE_OVERLOADING)
data StyleSchemeDescriptionPropertyInfo
instance AttrInfo StyleSchemeDescriptionPropertyInfo where
    type AttrAllowedOps StyleSchemeDescriptionPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StyleSchemeDescriptionPropertyInfo = IsStyleScheme
    type AttrSetTypeConstraint StyleSchemeDescriptionPropertyInfo = (~) ()
    type AttrTransferTypeConstraint StyleSchemeDescriptionPropertyInfo = (~) ()
    type AttrTransferType StyleSchemeDescriptionPropertyInfo = ()
    type AttrGetType StyleSchemeDescriptionPropertyInfo = (Maybe T.Text)
    type AttrLabel StyleSchemeDescriptionPropertyInfo = "description"
    type AttrOrigin StyleSchemeDescriptionPropertyInfo = StyleScheme
    attrGet = getStyleSchemeDescription
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.description"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#g:attr:description"
        })
#endif

-- VVV Prop "filename"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@filename@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' styleScheme #filename
-- @
getStyleSchemeFilename :: (MonadIO m, IsStyleScheme o) => o -> m (Maybe T.Text)
getStyleSchemeFilename :: forall (m :: * -> *) o.
(MonadIO m, IsStyleScheme o) =>
o -> m (Maybe Text)
getStyleSchemeFilename o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"filename"

#if defined(ENABLE_OVERLOADING)
data StyleSchemeFilenamePropertyInfo
instance AttrInfo StyleSchemeFilenamePropertyInfo where
    type AttrAllowedOps StyleSchemeFilenamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StyleSchemeFilenamePropertyInfo = IsStyleScheme
    type AttrSetTypeConstraint StyleSchemeFilenamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint StyleSchemeFilenamePropertyInfo = (~) ()
    type AttrTransferType StyleSchemeFilenamePropertyInfo = ()
    type AttrGetType StyleSchemeFilenamePropertyInfo = (Maybe T.Text)
    type AttrLabel StyleSchemeFilenamePropertyInfo = "filename"
    type AttrOrigin StyleSchemeFilenamePropertyInfo = StyleScheme
    attrGet = getStyleSchemeFilename
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.filename"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#g:attr:filename"
        })
#endif

-- VVV Prop "id"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' styleScheme #id
-- @
getStyleSchemeId :: (MonadIO m, IsStyleScheme o) => o -> m T.Text
getStyleSchemeId :: forall (m :: * -> *) o. (MonadIO m, IsStyleScheme o) => o -> m Text
getStyleSchemeId o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getStyleSchemeId" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"id"

-- | Construct a `GValueConstruct` with valid value for the “@id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStyleSchemeId :: (IsStyleScheme o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructStyleSchemeId :: forall o (m :: * -> *).
(IsStyleScheme o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructStyleSchemeId Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"id" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data StyleSchemeIdPropertyInfo
instance AttrInfo StyleSchemeIdPropertyInfo where
    type AttrAllowedOps StyleSchemeIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StyleSchemeIdPropertyInfo = IsStyleScheme
    type AttrSetTypeConstraint StyleSchemeIdPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint StyleSchemeIdPropertyInfo = (~) T.Text
    type AttrTransferType StyleSchemeIdPropertyInfo = T.Text
    type AttrGetType StyleSchemeIdPropertyInfo = T.Text
    type AttrLabel StyleSchemeIdPropertyInfo = "id"
    type AttrOrigin StyleSchemeIdPropertyInfo = StyleScheme
    attrGet = getStyleSchemeId
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructStyleSchemeId
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.id"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#g:attr:id"
        })
#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' styleScheme #name
-- @
getStyleSchemeName :: (MonadIO m, IsStyleScheme o) => o -> m T.Text
getStyleSchemeName :: forall (m :: * -> *) o. (MonadIO m, IsStyleScheme o) => o -> m Text
getStyleSchemeName o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getStyleSchemeName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"

#if defined(ENABLE_OVERLOADING)
data StyleSchemeNamePropertyInfo
instance AttrInfo StyleSchemeNamePropertyInfo where
    type AttrAllowedOps StyleSchemeNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StyleSchemeNamePropertyInfo = IsStyleScheme
    type AttrSetTypeConstraint StyleSchemeNamePropertyInfo = (~) ()
    type AttrTransferTypeConstraint StyleSchemeNamePropertyInfo = (~) ()
    type AttrTransferType StyleSchemeNamePropertyInfo = ()
    type AttrGetType StyleSchemeNamePropertyInfo = T.Text
    type AttrLabel StyleSchemeNamePropertyInfo = "name"
    type AttrOrigin StyleSchemeNamePropertyInfo = StyleScheme
    attrGet = getStyleSchemeName
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#g:attr:name"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StyleScheme
type instance O.AttributeList StyleScheme = StyleSchemeAttributeList
type StyleSchemeAttributeList = ('[ '("description", StyleSchemeDescriptionPropertyInfo), '("filename", StyleSchemeFilenamePropertyInfo), '("id", StyleSchemeIdPropertyInfo), '("name", StyleSchemeNamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
styleSchemeDescription :: AttrLabelProxy "description"
styleSchemeDescription = AttrLabelProxy

styleSchemeFilename :: AttrLabelProxy "filename"
styleSchemeFilename = AttrLabelProxy

styleSchemeId :: AttrLabelProxy "id"
styleSchemeId = AttrLabelProxy

styleSchemeName :: AttrLabelProxy "name"
styleSchemeName = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StyleScheme = StyleSchemeSignalList
type StyleSchemeSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method StyleScheme::get_authors
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scheme"
--           , argType =
--               TInterface Name { namespace = "GtkSource" , name = "StyleScheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleScheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_get_authors" gtk_source_style_scheme_get_authors :: 
    Ptr StyleScheme ->                      -- scheme : TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
    IO (Ptr CString)

-- | /No description available in the introspection data./
-- 
-- /Since: 2.0/
styleSchemeGetAuthors ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleScheme a) =>
    a
    -- ^ /@scheme@/: a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'.
    -> m (Maybe [T.Text])
    -- ^ __Returns:__ a
    -- 'P.Nothing'-terminated array containing the /@scheme@/ authors or 'P.Nothing' if
    -- no author is specified by the style scheme.
styleSchemeGetAuthors :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleScheme a) =>
a -> m (Maybe [Text])
styleSchemeGetAuthors a
scheme = 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
$ do
    Ptr StyleScheme
scheme' <- a -> IO (Ptr StyleScheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
scheme
    Ptr CString
result <- Ptr StyleScheme -> IO (Ptr CString)
gtk_source_style_scheme_get_authors Ptr StyleScheme
scheme'
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
scheme
    Maybe [Text] -> IO (Maybe [Text])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

#if defined(ENABLE_OVERLOADING)
data StyleSchemeGetAuthorsMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m, IsStyleScheme a) => O.OverloadedMethod StyleSchemeGetAuthorsMethodInfo a signature where
    overloadedMethod = styleSchemeGetAuthors

instance O.OverloadedMethodInfo StyleSchemeGetAuthorsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.styleSchemeGetAuthors",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#v:styleSchemeGetAuthors"
        })


#endif

-- method StyleScheme::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scheme"
--           , argType =
--               TInterface Name { namespace = "GtkSource" , name = "StyleScheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleScheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_get_description" gtk_source_style_scheme_get_description :: 
    Ptr StyleScheme ->                      -- scheme : TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 2.0/
styleSchemeGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleScheme a) =>
    a
    -- ^ /@scheme@/: a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ /@scheme@/ description (if defined), or 'P.Nothing'.
styleSchemeGetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleScheme a) =>
a -> m (Maybe Text)
styleSchemeGetDescription a
scheme = 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
$ do
    Ptr StyleScheme
scheme' <- a -> IO (Ptr StyleScheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
scheme
    CString
result <- Ptr StyleScheme -> IO CString
gtk_source_style_scheme_get_description Ptr StyleScheme
scheme'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
scheme
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data StyleSchemeGetDescriptionMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsStyleScheme a) => O.OverloadedMethod StyleSchemeGetDescriptionMethodInfo a signature where
    overloadedMethod = styleSchemeGetDescription

instance O.OverloadedMethodInfo StyleSchemeGetDescriptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.styleSchemeGetDescription",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#v:styleSchemeGetDescription"
        })


#endif

-- method StyleScheme::get_filename
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scheme"
--           , argType =
--               TInterface Name { namespace = "GtkSource" , name = "StyleScheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleScheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_get_filename" gtk_source_style_scheme_get_filename :: 
    Ptr StyleScheme ->                      -- scheme : TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 2.0/
styleSchemeGetFilename ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleScheme a) =>
    a
    -- ^ /@scheme@/: a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ /@scheme@/ file name if the scheme was created
    -- parsing a style scheme file or 'P.Nothing' in the other cases.
styleSchemeGetFilename :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleScheme a) =>
a -> m (Maybe Text)
styleSchemeGetFilename a
scheme = 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
$ do
    Ptr StyleScheme
scheme' <- a -> IO (Ptr StyleScheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
scheme
    CString
result <- Ptr StyleScheme -> IO CString
gtk_source_style_scheme_get_filename Ptr StyleScheme
scheme'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
scheme
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data StyleSchemeGetFilenameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsStyleScheme a) => O.OverloadedMethod StyleSchemeGetFilenameMethodInfo a signature where
    overloadedMethod = styleSchemeGetFilename

instance O.OverloadedMethodInfo StyleSchemeGetFilenameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.styleSchemeGetFilename",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#v:styleSchemeGetFilename"
        })


#endif

-- method StyleScheme::get_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scheme"
--           , argType =
--               TInterface Name { namespace = "GtkSource" , name = "StyleScheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleScheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_get_id" gtk_source_style_scheme_get_id :: 
    Ptr StyleScheme ->                      -- scheme : TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 2.0/
styleSchemeGetId ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleScheme a) =>
    a
    -- ^ /@scheme@/: a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'.
    -> m T.Text
    -- ^ __Returns:__ /@scheme@/ id.
styleSchemeGetId :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleScheme a) =>
a -> m Text
styleSchemeGetId a
scheme = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleScheme
scheme' <- a -> IO (Ptr StyleScheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
scheme
    CString
result <- Ptr StyleScheme -> IO CString
gtk_source_style_scheme_get_id Ptr StyleScheme
scheme'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleSchemeGetId" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
scheme
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data StyleSchemeGetIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsStyleScheme a) => O.OverloadedMethod StyleSchemeGetIdMethodInfo a signature where
    overloadedMethod = styleSchemeGetId

instance O.OverloadedMethodInfo StyleSchemeGetIdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.styleSchemeGetId",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#v:styleSchemeGetId"
        })


#endif

-- method StyleScheme::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scheme"
--           , argType =
--               TInterface Name { namespace = "GtkSource" , name = "StyleScheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleScheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_get_name" gtk_source_style_scheme_get_name :: 
    Ptr StyleScheme ->                      -- scheme : TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 2.0/
styleSchemeGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleScheme a) =>
    a
    -- ^ /@scheme@/: a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'.
    -> m T.Text
    -- ^ __Returns:__ /@scheme@/ name.
styleSchemeGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleScheme a) =>
a -> m Text
styleSchemeGetName a
scheme = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleScheme
scheme' <- a -> IO (Ptr StyleScheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
scheme
    CString
result <- Ptr StyleScheme -> IO CString
gtk_source_style_scheme_get_name Ptr StyleScheme
scheme'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleSchemeGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
scheme
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data StyleSchemeGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsStyleScheme a) => O.OverloadedMethod StyleSchemeGetNameMethodInfo a signature where
    overloadedMethod = styleSchemeGetName

instance O.OverloadedMethodInfo StyleSchemeGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.styleSchemeGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#v:styleSchemeGetName"
        })


#endif

-- method StyleScheme::get_style
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scheme"
--           , argType =
--               TInterface Name { namespace = "GtkSource" , name = "StyleScheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleScheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "style_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "id of the style to retrieve."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GtkSource" , name = "Style" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_get_style" gtk_source_style_scheme_get_style :: 
    Ptr StyleScheme ->                      -- scheme : TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
    CString ->                              -- style_id : TBasicType TUTF8
    IO (Ptr GtkSource.Style.Style)

-- | /No description available in the introspection data./
-- 
-- /Since: 2.0/
styleSchemeGetStyle ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleScheme a) =>
    a
    -- ^ /@scheme@/: a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'.
    -> T.Text
    -- ^ /@styleId@/: id of the style to retrieve.
    -> m (Maybe GtkSource.Style.Style)
    -- ^ __Returns:__ style which corresponds to /@styleId@/ in
    -- the /@scheme@/, or 'P.Nothing' when no style with this name found.  It is owned by
    -- /@scheme@/ and may not be unref\'ed.
styleSchemeGetStyle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleScheme a) =>
a -> Text -> m (Maybe Style)
styleSchemeGetStyle a
scheme Text
styleId = IO (Maybe Style) -> m (Maybe Style)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Style) -> m (Maybe Style))
-> IO (Maybe Style) -> m (Maybe Style)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleScheme
scheme' <- a -> IO (Ptr StyleScheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
scheme
    CString
styleId' <- Text -> IO CString
textToCString Text
styleId
    Ptr Style
result <- Ptr StyleScheme -> CString -> IO (Ptr Style)
gtk_source_style_scheme_get_style Ptr StyleScheme
scheme' CString
styleId'
    Maybe Style
maybeResult <- Ptr Style -> (Ptr Style -> IO Style) -> IO (Maybe Style)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Style
result ((Ptr Style -> IO Style) -> IO (Maybe Style))
-> (Ptr Style -> IO Style) -> IO (Maybe Style)
forall a b. (a -> b) -> a -> b
$ \Ptr Style
result' -> do
        Style
result'' <- ((ManagedPtr Style -> Style) -> Ptr Style -> IO Style
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Style -> Style
GtkSource.Style.Style) Ptr Style
result'
        Style -> IO Style
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Style
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
scheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
styleId'
    Maybe Style -> IO (Maybe Style)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Style
maybeResult

#if defined(ENABLE_OVERLOADING)
data StyleSchemeGetStyleMethodInfo
instance (signature ~ (T.Text -> m (Maybe GtkSource.Style.Style)), MonadIO m, IsStyleScheme a) => O.OverloadedMethod StyleSchemeGetStyleMethodInfo a signature where
    overloadedMethod = styleSchemeGetStyle

instance O.OverloadedMethodInfo StyleSchemeGetStyleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleScheme.styleSchemeGetStyle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-3.0.26/docs/GI-GtkSource-Objects-StyleScheme.html#v:styleSchemeGetStyle"
        })


#endif