{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.NM.Objects.SettingMatch
(
SettingMatch(..) ,
IsSettingMatch ,
toSettingMatch ,
#if defined(ENABLE_OVERLOADING)
ResolveSettingMatchMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SettingMatchAddDriverMethodInfo ,
#endif
settingMatchAddDriver ,
#if defined(ENABLE_OVERLOADING)
SettingMatchAddInterfaceNameMethodInfo ,
#endif
settingMatchAddInterfaceName ,
#if defined(ENABLE_OVERLOADING)
SettingMatchAddKernelCommandLineMethodInfo,
#endif
settingMatchAddKernelCommandLine ,
#if defined(ENABLE_OVERLOADING)
SettingMatchAddPathMethodInfo ,
#endif
settingMatchAddPath ,
#if defined(ENABLE_OVERLOADING)
SettingMatchClearDriversMethodInfo ,
#endif
settingMatchClearDrivers ,
#if defined(ENABLE_OVERLOADING)
SettingMatchClearInterfaceNamesMethodInfo,
#endif
settingMatchClearInterfaceNames ,
#if defined(ENABLE_OVERLOADING)
SettingMatchClearKernelCommandLinesMethodInfo,
#endif
settingMatchClearKernelCommandLines ,
#if defined(ENABLE_OVERLOADING)
SettingMatchClearPathsMethodInfo ,
#endif
settingMatchClearPaths ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetDriverMethodInfo ,
#endif
settingMatchGetDriver ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetDriversMethodInfo ,
#endif
settingMatchGetDrivers ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetInterfaceNameMethodInfo ,
#endif
settingMatchGetInterfaceName ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetInterfaceNamesMethodInfo ,
#endif
settingMatchGetInterfaceNames ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetKernelCommandLineMethodInfo,
#endif
settingMatchGetKernelCommandLine ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetKernelCommandLinesMethodInfo,
#endif
settingMatchGetKernelCommandLines ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetNumDriversMethodInfo ,
#endif
settingMatchGetNumDrivers ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetNumInterfaceNamesMethodInfo,
#endif
settingMatchGetNumInterfaceNames ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetNumKernelCommandLinesMethodInfo,
#endif
settingMatchGetNumKernelCommandLines ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetNumPathsMethodInfo ,
#endif
settingMatchGetNumPaths ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetPathMethodInfo ,
#endif
settingMatchGetPath ,
#if defined(ENABLE_OVERLOADING)
SettingMatchGetPathsMethodInfo ,
#endif
settingMatchGetPaths ,
settingMatchNew ,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemoveDriverMethodInfo ,
#endif
settingMatchRemoveDriver ,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemoveDriverByValueMethodInfo,
#endif
settingMatchRemoveDriverByValue ,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemoveInterfaceNameMethodInfo,
#endif
settingMatchRemoveInterfaceName ,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemoveInterfaceNameByValueMethodInfo,
#endif
settingMatchRemoveInterfaceNameByValue ,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemoveKernelCommandLineMethodInfo,
#endif
settingMatchRemoveKernelCommandLine ,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemoveKernelCommandLineByValueMethodInfo,
#endif
settingMatchRemoveKernelCommandLineByValue,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemovePathMethodInfo ,
#endif
settingMatchRemovePath ,
#if defined(ENABLE_OVERLOADING)
SettingMatchRemovePathByValueMethodInfo ,
#endif
settingMatchRemovePathByValue ,
#if defined(ENABLE_OVERLOADING)
SettingMatchDriverPropertyInfo ,
#endif
clearSettingMatchDriver ,
constructSettingMatchDriver ,
getSettingMatchDriver ,
setSettingMatchDriver ,
#if defined(ENABLE_OVERLOADING)
settingMatchDriver ,
#endif
#if defined(ENABLE_OVERLOADING)
SettingMatchInterfaceNamePropertyInfo ,
#endif
clearSettingMatchInterfaceName ,
constructSettingMatchInterfaceName ,
getSettingMatchInterfaceName ,
setSettingMatchInterfaceName ,
#if defined(ENABLE_OVERLOADING)
settingMatchInterfaceName ,
#endif
#if defined(ENABLE_OVERLOADING)
SettingMatchKernelCommandLinePropertyInfo,
#endif
clearSettingMatchKernelCommandLine ,
constructSettingMatchKernelCommandLine ,
getSettingMatchKernelCommandLine ,
setSettingMatchKernelCommandLine ,
#if defined(ENABLE_OVERLOADING)
settingMatchKernelCommandLine ,
#endif
#if defined(ENABLE_OVERLOADING)
SettingMatchPathPropertyInfo ,
#endif
clearSettingMatchPath ,
constructSettingMatchPath ,
getSettingMatchPath ,
setSettingMatchPath ,
#if defined(ENABLE_OVERLOADING)
settingMatchPath ,
#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.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.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.NM.Callbacks as NM.Callbacks
import {-# SOURCE #-} qualified GI.NM.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Flags as NM.Flags
import {-# SOURCE #-} qualified GI.NM.Interfaces.Connection as NM.Connection
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.Setting8021x as NM.Setting8021x
import {-# SOURCE #-} qualified GI.NM.Objects.SettingAdsl as NM.SettingAdsl
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBluetooth as NM.SettingBluetooth
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBond as NM.SettingBond
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridge as NM.SettingBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridgePort as NM.SettingBridgePort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingCdma as NM.SettingCdma
import {-# SOURCE #-} qualified GI.NM.Objects.SettingConnection as NM.SettingConnection
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDcb as NM.SettingDcb
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDummy as NM.SettingDummy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGeneric as NM.SettingGeneric
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGsm as NM.SettingGsm
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP4Config as NM.SettingIP4Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP6Config as NM.SettingIP6Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPConfig as NM.SettingIPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPTunnel as NM.SettingIPTunnel
import {-# SOURCE #-} qualified GI.NM.Objects.SettingInfiniband as NM.SettingInfiniband
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacsec as NM.SettingMacsec
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacvlan as NM.SettingMacvlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOlpcMesh as NM.SettingOlpcMesh
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsBridge as NM.SettingOvsBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsInterface as NM.SettingOvsInterface
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPatch as NM.SettingOvsPatch
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPort as NM.SettingOvsPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPpp as NM.SettingPpp
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPppoe as NM.SettingPppoe
import {-# SOURCE #-} qualified GI.NM.Objects.SettingProxy as NM.SettingProxy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingSerial as NM.SettingSerial
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTCConfig as NM.SettingTCConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeam as NM.SettingTeam
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeamPort as NM.SettingTeamPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTun as NM.SettingTun
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVlan as NM.SettingVlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVpn as NM.SettingVpn
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVxlan as NM.SettingVxlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWimax as NM.SettingWimax
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWired as NM.SettingWired
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWireless as NM.SettingWireless
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWirelessSecurity as NM.SettingWirelessSecurity
import {-# SOURCE #-} qualified GI.NM.Structs.BridgeVlan as NM.BridgeVlan
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoutingRule as NM.IPRoutingRule
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
#endif
newtype SettingMatch = SettingMatch (SP.ManagedPtr SettingMatch)
deriving (SettingMatch -> SettingMatch -> Bool
(SettingMatch -> SettingMatch -> Bool)
-> (SettingMatch -> SettingMatch -> Bool) -> Eq SettingMatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SettingMatch -> SettingMatch -> Bool
== :: SettingMatch -> SettingMatch -> Bool
$c/= :: SettingMatch -> SettingMatch -> Bool
/= :: SettingMatch -> SettingMatch -> Bool
Eq)
instance SP.ManagedPtrNewtype SettingMatch where
toManagedPtr :: SettingMatch -> ManagedPtr SettingMatch
toManagedPtr (SettingMatch ManagedPtr SettingMatch
p) = ManagedPtr SettingMatch
p
foreign import ccall "nm_setting_match_get_type"
c_nm_setting_match_get_type :: IO B.Types.GType
instance B.Types.TypedObject SettingMatch where
glibType :: IO GType
glibType = IO GType
c_nm_setting_match_get_type
instance B.Types.GObject SettingMatch
class (SP.GObject o, O.IsDescendantOf SettingMatch o) => IsSettingMatch o
instance (SP.GObject o, O.IsDescendantOf SettingMatch o) => IsSettingMatch o
instance O.HasParentTypes SettingMatch
type instance O.ParentTypes SettingMatch = '[NM.Setting.Setting, GObject.Object.Object]
toSettingMatch :: (MIO.MonadIO m, IsSettingMatch o) => o -> m SettingMatch
toSettingMatch :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> m SettingMatch
toSettingMatch = IO SettingMatch -> m SettingMatch
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SettingMatch -> m SettingMatch)
-> (o -> IO SettingMatch) -> o -> m SettingMatch
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SettingMatch -> SettingMatch) -> o -> IO SettingMatch
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SettingMatch -> SettingMatch
SettingMatch
instance B.GValue.IsGValue (Maybe SettingMatch) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_nm_setting_match_get_type
gvalueSet_ :: Ptr GValue -> Maybe SettingMatch -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SettingMatch
P.Nothing = Ptr GValue -> Ptr SettingMatch -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SettingMatch
forall a. Ptr a
FP.nullPtr :: FP.Ptr SettingMatch)
gvalueSet_ Ptr GValue
gv (P.Just SettingMatch
obj) = SettingMatch -> (Ptr SettingMatch -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SettingMatch
obj (Ptr GValue -> Ptr SettingMatch -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe SettingMatch)
gvalueGet_ Ptr GValue
gv = do
Ptr SettingMatch
ptr <- Ptr GValue -> IO (Ptr SettingMatch)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SettingMatch)
if Ptr SettingMatch
ptr Ptr SettingMatch -> Ptr SettingMatch -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SettingMatch
forall a. Ptr a
FP.nullPtr
then SettingMatch -> Maybe SettingMatch
forall a. a -> Maybe a
P.Just (SettingMatch -> Maybe SettingMatch)
-> IO SettingMatch -> IO (Maybe SettingMatch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr SettingMatch -> SettingMatch)
-> Ptr SettingMatch -> IO SettingMatch
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SettingMatch -> SettingMatch
SettingMatch Ptr SettingMatch
ptr
else Maybe SettingMatch -> IO (Maybe SettingMatch)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SettingMatch
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSettingMatchMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveSettingMatchMethod "addDriver" o = SettingMatchAddDriverMethodInfo
ResolveSettingMatchMethod "addInterfaceName" o = SettingMatchAddInterfaceNameMethodInfo
ResolveSettingMatchMethod "addKernelCommandLine" o = SettingMatchAddKernelCommandLineMethodInfo
ResolveSettingMatchMethod "addPath" o = SettingMatchAddPathMethodInfo
ResolveSettingMatchMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSettingMatchMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSettingMatchMethod "clearDrivers" o = SettingMatchClearDriversMethodInfo
ResolveSettingMatchMethod "clearInterfaceNames" o = SettingMatchClearInterfaceNamesMethodInfo
ResolveSettingMatchMethod "clearKernelCommandLines" o = SettingMatchClearKernelCommandLinesMethodInfo
ResolveSettingMatchMethod "clearPaths" o = SettingMatchClearPathsMethodInfo
ResolveSettingMatchMethod "compare" o = NM.Setting.SettingCompareMethodInfo
ResolveSettingMatchMethod "diff" o = NM.Setting.SettingDiffMethodInfo
ResolveSettingMatchMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
ResolveSettingMatchMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
ResolveSettingMatchMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSettingMatchMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSettingMatchMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSettingMatchMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSettingMatchMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSettingMatchMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSettingMatchMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
ResolveSettingMatchMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
ResolveSettingMatchMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
ResolveSettingMatchMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
ResolveSettingMatchMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
ResolveSettingMatchMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
ResolveSettingMatchMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
ResolveSettingMatchMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
ResolveSettingMatchMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSettingMatchMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSettingMatchMethod "removeDriver" o = SettingMatchRemoveDriverMethodInfo
ResolveSettingMatchMethod "removeDriverByValue" o = SettingMatchRemoveDriverByValueMethodInfo
ResolveSettingMatchMethod "removeInterfaceName" o = SettingMatchRemoveInterfaceNameMethodInfo
ResolveSettingMatchMethod "removeInterfaceNameByValue" o = SettingMatchRemoveInterfaceNameByValueMethodInfo
ResolveSettingMatchMethod "removeKernelCommandLine" o = SettingMatchRemoveKernelCommandLineMethodInfo
ResolveSettingMatchMethod "removeKernelCommandLineByValue" o = SettingMatchRemoveKernelCommandLineByValueMethodInfo
ResolveSettingMatchMethod "removePath" o = SettingMatchRemovePathMethodInfo
ResolveSettingMatchMethod "removePathByValue" o = SettingMatchRemovePathByValueMethodInfo
ResolveSettingMatchMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSettingMatchMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSettingMatchMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSettingMatchMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSettingMatchMethod "toString" o = NM.Setting.SettingToStringMethodInfo
ResolveSettingMatchMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSettingMatchMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
ResolveSettingMatchMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
ResolveSettingMatchMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSettingMatchMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSettingMatchMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
ResolveSettingMatchMethod "getDriver" o = SettingMatchGetDriverMethodInfo
ResolveSettingMatchMethod "getDrivers" o = SettingMatchGetDriversMethodInfo
ResolveSettingMatchMethod "getInterfaceName" o = SettingMatchGetInterfaceNameMethodInfo
ResolveSettingMatchMethod "getInterfaceNames" o = SettingMatchGetInterfaceNamesMethodInfo
ResolveSettingMatchMethod "getKernelCommandLine" o = SettingMatchGetKernelCommandLineMethodInfo
ResolveSettingMatchMethod "getKernelCommandLines" o = SettingMatchGetKernelCommandLinesMethodInfo
ResolveSettingMatchMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
ResolveSettingMatchMethod "getNumDrivers" o = SettingMatchGetNumDriversMethodInfo
ResolveSettingMatchMethod "getNumInterfaceNames" o = SettingMatchGetNumInterfaceNamesMethodInfo
ResolveSettingMatchMethod "getNumKernelCommandLines" o = SettingMatchGetNumKernelCommandLinesMethodInfo
ResolveSettingMatchMethod "getNumPaths" o = SettingMatchGetNumPathsMethodInfo
ResolveSettingMatchMethod "getPath" o = SettingMatchGetPathMethodInfo
ResolveSettingMatchMethod "getPaths" o = SettingMatchGetPathsMethodInfo
ResolveSettingMatchMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSettingMatchMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSettingMatchMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
ResolveSettingMatchMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSettingMatchMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSettingMatchMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSettingMatchMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
ResolveSettingMatchMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSettingMatchMethod t SettingMatch, O.OverloadedMethod info SettingMatch p) => OL.IsLabel t (SettingMatch -> 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 ~ ResolveSettingMatchMethod t SettingMatch, O.OverloadedMethod info SettingMatch p, R.HasField t SettingMatch p) => R.HasField t SettingMatch p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSettingMatchMethod t SettingMatch, O.OverloadedMethodInfo info SettingMatch) => OL.IsLabel t (O.MethodProxy info SettingMatch) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getSettingMatchDriver :: (MonadIO m, IsSettingMatch o) => o -> m (Maybe [T.Text])
getSettingMatchDriver :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> m (Maybe [Text])
getSettingMatchDriver 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.getObjectPropertyStringArray o
obj String
"driver"
setSettingMatchDriver :: (MonadIO m, IsSettingMatch o) => o -> [T.Text] -> m ()
setSettingMatchDriver :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> [Text] -> m ()
setSettingMatchDriver o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"driver" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructSettingMatchDriver :: (IsSettingMatch o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructSettingMatchDriver :: forall o (m :: * -> *).
(IsSettingMatch o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructSettingMatchDriver [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.constructObjectPropertyStringArray String
"driver" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearSettingMatchDriver :: (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchDriver :: forall (m :: * -> *) o. (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchDriver o
obj = 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
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"driver" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data SettingMatchDriverPropertyInfo
instance AttrInfo SettingMatchDriverPropertyInfo where
type AttrAllowedOps SettingMatchDriverPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SettingMatchDriverPropertyInfo = IsSettingMatch
type AttrSetTypeConstraint SettingMatchDriverPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint SettingMatchDriverPropertyInfo = (~) [T.Text]
type AttrTransferType SettingMatchDriverPropertyInfo = [T.Text]
type AttrGetType SettingMatchDriverPropertyInfo = (Maybe [T.Text])
type AttrLabel SettingMatchDriverPropertyInfo = "driver"
type AttrOrigin SettingMatchDriverPropertyInfo = SettingMatch
attrGet = getSettingMatchDriver
attrSet = setSettingMatchDriver
attrTransfer _ v = do
return v
attrConstruct = constructSettingMatchDriver
attrClear = clearSettingMatchDriver
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.driver"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#g:attr:driver"
})
#endif
getSettingMatchInterfaceName :: (MonadIO m, IsSettingMatch o) => o -> m (Maybe [T.Text])
getSettingMatchInterfaceName :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> m (Maybe [Text])
getSettingMatchInterfaceName 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.getObjectPropertyStringArray o
obj String
"interface-name"
setSettingMatchInterfaceName :: (MonadIO m, IsSettingMatch o) => o -> [T.Text] -> m ()
setSettingMatchInterfaceName :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> [Text] -> m ()
setSettingMatchInterfaceName o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"interface-name" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructSettingMatchInterfaceName :: (IsSettingMatch o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructSettingMatchInterfaceName :: forall o (m :: * -> *).
(IsSettingMatch o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructSettingMatchInterfaceName [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.constructObjectPropertyStringArray String
"interface-name" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearSettingMatchInterfaceName :: (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchInterfaceName :: forall (m :: * -> *) o. (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchInterfaceName o
obj = 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
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"interface-name" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data SettingMatchInterfaceNamePropertyInfo
instance AttrInfo SettingMatchInterfaceNamePropertyInfo where
type AttrAllowedOps SettingMatchInterfaceNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SettingMatchInterfaceNamePropertyInfo = IsSettingMatch
type AttrSetTypeConstraint SettingMatchInterfaceNamePropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint SettingMatchInterfaceNamePropertyInfo = (~) [T.Text]
type AttrTransferType SettingMatchInterfaceNamePropertyInfo = [T.Text]
type AttrGetType SettingMatchInterfaceNamePropertyInfo = (Maybe [T.Text])
type AttrLabel SettingMatchInterfaceNamePropertyInfo = "interface-name"
type AttrOrigin SettingMatchInterfaceNamePropertyInfo = SettingMatch
attrGet = getSettingMatchInterfaceName
attrSet = setSettingMatchInterfaceName
attrTransfer _ v = do
return v
attrConstruct = constructSettingMatchInterfaceName
attrClear = clearSettingMatchInterfaceName
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.interfaceName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#g:attr:interfaceName"
})
#endif
getSettingMatchKernelCommandLine :: (MonadIO m, IsSettingMatch o) => o -> m (Maybe [T.Text])
getSettingMatchKernelCommandLine :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> m (Maybe [Text])
getSettingMatchKernelCommandLine 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.getObjectPropertyStringArray o
obj String
"kernel-command-line"
setSettingMatchKernelCommandLine :: (MonadIO m, IsSettingMatch o) => o -> [T.Text] -> m ()
setSettingMatchKernelCommandLine :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> [Text] -> m ()
setSettingMatchKernelCommandLine o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"kernel-command-line" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructSettingMatchKernelCommandLine :: (IsSettingMatch o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructSettingMatchKernelCommandLine :: forall o (m :: * -> *).
(IsSettingMatch o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructSettingMatchKernelCommandLine [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.constructObjectPropertyStringArray String
"kernel-command-line" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearSettingMatchKernelCommandLine :: (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchKernelCommandLine :: forall (m :: * -> *) o. (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchKernelCommandLine o
obj = 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
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"kernel-command-line" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data SettingMatchKernelCommandLinePropertyInfo
instance AttrInfo SettingMatchKernelCommandLinePropertyInfo where
type AttrAllowedOps SettingMatchKernelCommandLinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SettingMatchKernelCommandLinePropertyInfo = IsSettingMatch
type AttrSetTypeConstraint SettingMatchKernelCommandLinePropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint SettingMatchKernelCommandLinePropertyInfo = (~) [T.Text]
type AttrTransferType SettingMatchKernelCommandLinePropertyInfo = [T.Text]
type AttrGetType SettingMatchKernelCommandLinePropertyInfo = (Maybe [T.Text])
type AttrLabel SettingMatchKernelCommandLinePropertyInfo = "kernel-command-line"
type AttrOrigin SettingMatchKernelCommandLinePropertyInfo = SettingMatch
attrGet = getSettingMatchKernelCommandLine
attrSet = setSettingMatchKernelCommandLine
attrTransfer _ v = do
return v
attrConstruct = constructSettingMatchKernelCommandLine
attrClear = clearSettingMatchKernelCommandLine
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.kernelCommandLine"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#g:attr:kernelCommandLine"
})
#endif
getSettingMatchPath :: (MonadIO m, IsSettingMatch o) => o -> m (Maybe [T.Text])
getSettingMatchPath :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> m (Maybe [Text])
getSettingMatchPath 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.getObjectPropertyStringArray o
obj String
"path"
setSettingMatchPath :: (MonadIO m, IsSettingMatch o) => o -> [T.Text] -> m ()
setSettingMatchPath :: forall (m :: * -> *) o.
(MonadIO m, IsSettingMatch o) =>
o -> [Text] -> m ()
setSettingMatchPath o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"path" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructSettingMatchPath :: (IsSettingMatch o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructSettingMatchPath :: forall o (m :: * -> *).
(IsSettingMatch o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructSettingMatchPath [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.constructObjectPropertyStringArray String
"path" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearSettingMatchPath :: (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchPath :: forall (m :: * -> *) o. (MonadIO m, IsSettingMatch o) => o -> m ()
clearSettingMatchPath o
obj = 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
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"path" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data SettingMatchPathPropertyInfo
instance AttrInfo SettingMatchPathPropertyInfo where
type AttrAllowedOps SettingMatchPathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SettingMatchPathPropertyInfo = IsSettingMatch
type AttrSetTypeConstraint SettingMatchPathPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint SettingMatchPathPropertyInfo = (~) [T.Text]
type AttrTransferType SettingMatchPathPropertyInfo = [T.Text]
type AttrGetType SettingMatchPathPropertyInfo = (Maybe [T.Text])
type AttrLabel SettingMatchPathPropertyInfo = "path"
type AttrOrigin SettingMatchPathPropertyInfo = SettingMatch
attrGet = getSettingMatchPath
attrSet = setSettingMatchPath
attrTransfer _ v = do
return v
attrConstruct = constructSettingMatchPath
attrClear = clearSettingMatchPath
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.path"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#g:attr:path"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingMatch
type instance O.AttributeList SettingMatch = SettingMatchAttributeList
type SettingMatchAttributeList = ('[ '("driver", SettingMatchDriverPropertyInfo), '("interfaceName", SettingMatchInterfaceNamePropertyInfo), '("kernelCommandLine", SettingMatchKernelCommandLinePropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("path", SettingMatchPathPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
settingMatchDriver :: AttrLabelProxy "driver"
settingMatchDriver = AttrLabelProxy
settingMatchInterfaceName :: AttrLabelProxy "interfaceName"
settingMatchInterfaceName = AttrLabelProxy
settingMatchKernelCommandLine :: AttrLabelProxy "kernelCommandLine"
settingMatchKernelCommandLine = AttrLabelProxy
settingMatchPath :: AttrLabelProxy "path"
settingMatchPath = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SettingMatch = SettingMatchSignalList
type SettingMatchSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "nm_setting_match_new" nm_setting_match_new ::
IO (Ptr SettingMatch)
settingMatchNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m SettingMatch
settingMatchNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m SettingMatch
settingMatchNew = IO SettingMatch -> m SettingMatch
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingMatch -> m SettingMatch)
-> IO SettingMatch -> m SettingMatch
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingMatch
result <- IO (Ptr SettingMatch)
nm_setting_match_new
Text -> Ptr SettingMatch -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchNew" Ptr SettingMatch
result
SettingMatch
result' <- ((ManagedPtr SettingMatch -> SettingMatch)
-> Ptr SettingMatch -> IO SettingMatch
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SettingMatch -> SettingMatch
SettingMatch) Ptr SettingMatch
result
SettingMatch -> IO SettingMatch
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingMatch
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "nm_setting_match_add_driver" nm_setting_match_add_driver ::
Ptr SettingMatch ->
CString ->
IO ()
settingMatchAddDriver ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m ()
settingMatchAddDriver :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m ()
settingMatchAddDriver a
setting Text
driver = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
driver' <- Text -> IO CString
textToCString Text
driver
Ptr SettingMatch -> CString -> IO ()
nm_setting_match_add_driver Ptr SettingMatch
setting' CString
driver'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
driver'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchAddDriverMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchAddDriverMethodInfo a signature where
overloadedMethod = settingMatchAddDriver
instance O.OverloadedMethodInfo SettingMatchAddDriverMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchAddDriver",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchAddDriver"
})
#endif
foreign import ccall "nm_setting_match_add_interface_name" nm_setting_match_add_interface_name ::
Ptr SettingMatch ->
CString ->
IO ()
settingMatchAddInterfaceName ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m ()
settingMatchAddInterfaceName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m ()
settingMatchAddInterfaceName a
setting Text
interfaceName = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
Ptr SettingMatch -> CString -> IO ()
nm_setting_match_add_interface_name Ptr SettingMatch
setting' CString
interfaceName'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchAddInterfaceNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchAddInterfaceNameMethodInfo a signature where
overloadedMethod = settingMatchAddInterfaceName
instance O.OverloadedMethodInfo SettingMatchAddInterfaceNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchAddInterfaceName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchAddInterfaceName"
})
#endif
foreign import ccall "nm_setting_match_add_kernel_command_line" nm_setting_match_add_kernel_command_line ::
Ptr SettingMatch ->
CString ->
IO ()
settingMatchAddKernelCommandLine ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m ()
settingMatchAddKernelCommandLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m ()
settingMatchAddKernelCommandLine a
setting Text
kernelCommandLine = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
kernelCommandLine' <- Text -> IO CString
textToCString Text
kernelCommandLine
Ptr SettingMatch -> CString -> IO ()
nm_setting_match_add_kernel_command_line Ptr SettingMatch
setting' CString
kernelCommandLine'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
kernelCommandLine'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchAddKernelCommandLineMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchAddKernelCommandLineMethodInfo a signature where
overloadedMethod = settingMatchAddKernelCommandLine
instance O.OverloadedMethodInfo SettingMatchAddKernelCommandLineMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchAddKernelCommandLine",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchAddKernelCommandLine"
})
#endif
foreign import ccall "nm_setting_match_add_path" nm_setting_match_add_path ::
Ptr SettingMatch ->
CString ->
IO ()
settingMatchAddPath ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m ()
settingMatchAddPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m ()
settingMatchAddPath a
setting Text
path = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
path' <- Text -> IO CString
textToCString Text
path
Ptr SettingMatch -> CString -> IO ()
nm_setting_match_add_path Ptr SettingMatch
setting' CString
path'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchAddPathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchAddPathMethodInfo a signature where
overloadedMethod = settingMatchAddPath
instance O.OverloadedMethodInfo SettingMatchAddPathMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchAddPath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchAddPath"
})
#endif
foreign import ccall "nm_setting_match_clear_drivers" nm_setting_match_clear_drivers ::
Ptr SettingMatch ->
IO ()
settingMatchClearDrivers ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m ()
settingMatchClearDrivers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m ()
settingMatchClearDrivers a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> IO ()
nm_setting_match_clear_drivers Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchClearDriversMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchClearDriversMethodInfo a signature where
overloadedMethod = settingMatchClearDrivers
instance O.OverloadedMethodInfo SettingMatchClearDriversMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchClearDrivers",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchClearDrivers"
})
#endif
foreign import ccall "nm_setting_match_clear_interface_names" nm_setting_match_clear_interface_names ::
Ptr SettingMatch ->
IO ()
settingMatchClearInterfaceNames ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m ()
settingMatchClearInterfaceNames :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m ()
settingMatchClearInterfaceNames a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> IO ()
nm_setting_match_clear_interface_names Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchClearInterfaceNamesMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchClearInterfaceNamesMethodInfo a signature where
overloadedMethod = settingMatchClearInterfaceNames
instance O.OverloadedMethodInfo SettingMatchClearInterfaceNamesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchClearInterfaceNames",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchClearInterfaceNames"
})
#endif
foreign import ccall "nm_setting_match_clear_kernel_command_lines" nm_setting_match_clear_kernel_command_lines ::
Ptr SettingMatch ->
IO ()
settingMatchClearKernelCommandLines ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m ()
settingMatchClearKernelCommandLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m ()
settingMatchClearKernelCommandLines a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> IO ()
nm_setting_match_clear_kernel_command_lines Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchClearKernelCommandLinesMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchClearKernelCommandLinesMethodInfo a signature where
overloadedMethod = settingMatchClearKernelCommandLines
instance O.OverloadedMethodInfo SettingMatchClearKernelCommandLinesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchClearKernelCommandLines",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchClearKernelCommandLines"
})
#endif
foreign import ccall "nm_setting_match_clear_paths" nm_setting_match_clear_paths ::
Ptr SettingMatch ->
IO ()
settingMatchClearPaths ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m ()
settingMatchClearPaths :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m ()
settingMatchClearPaths a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> IO ()
nm_setting_match_clear_paths Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchClearPathsMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchClearPathsMethodInfo a signature where
overloadedMethod = settingMatchClearPaths
instance O.OverloadedMethodInfo SettingMatchClearPathsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchClearPaths",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchClearPaths"
})
#endif
foreign import ccall "nm_setting_match_get_driver" nm_setting_match_get_driver ::
Ptr SettingMatch ->
Word32 ->
IO CString
settingMatchGetDriver ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Word32
-> m T.Text
settingMatchGetDriver :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Word32 -> m Text
settingMatchGetDriver a
setting Word32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
result <- Ptr SettingMatch -> Word32 -> IO CString
nm_setting_match_get_driver Ptr SettingMatch
setting' Word32
idx
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetDriver" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetDriverMethodInfo
instance (signature ~ (Word32 -> m T.Text), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetDriverMethodInfo a signature where
overloadedMethod = settingMatchGetDriver
instance O.OverloadedMethodInfo SettingMatchGetDriverMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetDriver",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetDriver"
})
#endif
foreign import ccall "nm_setting_match_get_drivers" nm_setting_match_get_drivers ::
Ptr SettingMatch ->
Ptr Word32 ->
IO (Ptr CString)
settingMatchGetDrivers ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m [T.Text]
settingMatchGetDrivers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m [Text]
settingMatchGetDrivers a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr Word32
length_ <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr CString
result <- Ptr SettingMatch -> Ptr Word32 -> IO (Ptr CString)
nm_setting_match_get_drivers Ptr SettingMatch
setting' Ptr Word32
length_
Word32
length_' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
length_
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetDrivers" Ptr CString
result
[Text]
result' <- (Word32 -> Ptr CString -> IO [Text]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [Text]
unpackUTF8CArrayWithLength Word32
length_') Ptr CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
length_
[Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetDriversMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetDriversMethodInfo a signature where
overloadedMethod = settingMatchGetDrivers
instance O.OverloadedMethodInfo SettingMatchGetDriversMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetDrivers",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetDrivers"
})
#endif
foreign import ccall "nm_setting_match_get_interface_name" nm_setting_match_get_interface_name ::
Ptr SettingMatch ->
Int32 ->
IO CString
settingMatchGetInterfaceName ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Int32
-> m T.Text
settingMatchGetInterfaceName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Int32 -> m Text
settingMatchGetInterfaceName a
setting Int32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
result <- Ptr SettingMatch -> Int32 -> IO CString
nm_setting_match_get_interface_name Ptr SettingMatch
setting' Int32
idx
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetInterfaceName" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetInterfaceNameMethodInfo
instance (signature ~ (Int32 -> m T.Text), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetInterfaceNameMethodInfo a signature where
overloadedMethod = settingMatchGetInterfaceName
instance O.OverloadedMethodInfo SettingMatchGetInterfaceNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetInterfaceName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetInterfaceName"
})
#endif
foreign import ccall "nm_setting_match_get_interface_names" nm_setting_match_get_interface_names ::
Ptr SettingMatch ->
Ptr Word32 ->
IO (Ptr CString)
settingMatchGetInterfaceNames ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m [T.Text]
settingMatchGetInterfaceNames :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m [Text]
settingMatchGetInterfaceNames a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr Word32
length_ <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr CString
result <- Ptr SettingMatch -> Ptr Word32 -> IO (Ptr CString)
nm_setting_match_get_interface_names Ptr SettingMatch
setting' Ptr Word32
length_
Word32
length_' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
length_
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetInterfaceNames" Ptr CString
result
[Text]
result' <- (Word32 -> Ptr CString -> IO [Text]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [Text]
unpackUTF8CArrayWithLength Word32
length_') Ptr CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
length_
[Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetInterfaceNamesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetInterfaceNamesMethodInfo a signature where
overloadedMethod = settingMatchGetInterfaceNames
instance O.OverloadedMethodInfo SettingMatchGetInterfaceNamesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetInterfaceNames",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetInterfaceNames"
})
#endif
foreign import ccall "nm_setting_match_get_kernel_command_line" nm_setting_match_get_kernel_command_line ::
Ptr SettingMatch ->
Word32 ->
IO CString
settingMatchGetKernelCommandLine ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Word32
-> m T.Text
settingMatchGetKernelCommandLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Word32 -> m Text
settingMatchGetKernelCommandLine a
setting Word32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
result <- Ptr SettingMatch -> Word32 -> IO CString
nm_setting_match_get_kernel_command_line Ptr SettingMatch
setting' Word32
idx
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetKernelCommandLine" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetKernelCommandLineMethodInfo
instance (signature ~ (Word32 -> m T.Text), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetKernelCommandLineMethodInfo a signature where
overloadedMethod = settingMatchGetKernelCommandLine
instance O.OverloadedMethodInfo SettingMatchGetKernelCommandLineMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetKernelCommandLine",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetKernelCommandLine"
})
#endif
foreign import ccall "nm_setting_match_get_kernel_command_lines" nm_setting_match_get_kernel_command_lines ::
Ptr SettingMatch ->
Ptr Word32 ->
IO (Ptr CString)
settingMatchGetKernelCommandLines ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m [T.Text]
settingMatchGetKernelCommandLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m [Text]
settingMatchGetKernelCommandLines a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr Word32
length_ <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr CString
result <- Ptr SettingMatch -> Ptr Word32 -> IO (Ptr CString)
nm_setting_match_get_kernel_command_lines Ptr SettingMatch
setting' Ptr Word32
length_
Word32
length_' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
length_
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetKernelCommandLines" Ptr CString
result
[Text]
result' <- (Word32 -> Ptr CString -> IO [Text]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [Text]
unpackUTF8CArrayWithLength Word32
length_') Ptr CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
length_
[Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetKernelCommandLinesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetKernelCommandLinesMethodInfo a signature where
overloadedMethod = settingMatchGetKernelCommandLines
instance O.OverloadedMethodInfo SettingMatchGetKernelCommandLinesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetKernelCommandLines",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetKernelCommandLines"
})
#endif
foreign import ccall "nm_setting_match_get_num_drivers" nm_setting_match_get_num_drivers ::
Ptr SettingMatch ->
IO Word32
settingMatchGetNumDrivers ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m Word32
settingMatchGetNumDrivers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m Word32
settingMatchGetNumDrivers a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Word32
result <- Ptr SettingMatch -> IO Word32
nm_setting_match_get_num_drivers Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetNumDriversMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetNumDriversMethodInfo a signature where
overloadedMethod = settingMatchGetNumDrivers
instance O.OverloadedMethodInfo SettingMatchGetNumDriversMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetNumDrivers",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetNumDrivers"
})
#endif
foreign import ccall "nm_setting_match_get_num_interface_names" nm_setting_match_get_num_interface_names ::
Ptr SettingMatch ->
IO Word32
settingMatchGetNumInterfaceNames ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m Word32
settingMatchGetNumInterfaceNames :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m Word32
settingMatchGetNumInterfaceNames a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Word32
result <- Ptr SettingMatch -> IO Word32
nm_setting_match_get_num_interface_names Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetNumInterfaceNamesMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetNumInterfaceNamesMethodInfo a signature where
overloadedMethod = settingMatchGetNumInterfaceNames
instance O.OverloadedMethodInfo SettingMatchGetNumInterfaceNamesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetNumInterfaceNames",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetNumInterfaceNames"
})
#endif
foreign import ccall "nm_setting_match_get_num_kernel_command_lines" nm_setting_match_get_num_kernel_command_lines ::
Ptr SettingMatch ->
IO Word32
settingMatchGetNumKernelCommandLines ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m Word32
settingMatchGetNumKernelCommandLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m Word32
settingMatchGetNumKernelCommandLines a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Word32
result <- Ptr SettingMatch -> IO Word32
nm_setting_match_get_num_kernel_command_lines Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetNumKernelCommandLinesMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetNumKernelCommandLinesMethodInfo a signature where
overloadedMethod = settingMatchGetNumKernelCommandLines
instance O.OverloadedMethodInfo SettingMatchGetNumKernelCommandLinesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetNumKernelCommandLines",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetNumKernelCommandLines"
})
#endif
foreign import ccall "nm_setting_match_get_num_paths" nm_setting_match_get_num_paths ::
Ptr SettingMatch ->
IO Word32
settingMatchGetNumPaths ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m Word32
settingMatchGetNumPaths :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m Word32
settingMatchGetNumPaths a
setting = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Word32
result <- Ptr SettingMatch -> IO Word32
nm_setting_match_get_num_paths Ptr SettingMatch
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetNumPathsMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetNumPathsMethodInfo a signature where
overloadedMethod = settingMatchGetNumPaths
instance O.OverloadedMethodInfo SettingMatchGetNumPathsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetNumPaths",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetNumPaths"
})
#endif
foreign import ccall "nm_setting_match_get_path" nm_setting_match_get_path ::
Ptr SettingMatch ->
Word32 ->
IO CString
settingMatchGetPath ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Word32
-> m T.Text
settingMatchGetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Word32 -> m Text
settingMatchGetPath a
setting Word32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
result <- Ptr SettingMatch -> Word32 -> IO CString
nm_setting_match_get_path Ptr SettingMatch
setting' Word32
idx
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetPath" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetPathMethodInfo
instance (signature ~ (Word32 -> m T.Text), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetPathMethodInfo a signature where
overloadedMethod = settingMatchGetPath
instance O.OverloadedMethodInfo SettingMatchGetPathMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetPath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetPath"
})
#endif
foreign import ccall "nm_setting_match_get_paths" nm_setting_match_get_paths ::
Ptr SettingMatch ->
Ptr Word32 ->
IO (Ptr CString)
settingMatchGetPaths ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> m [T.Text]
settingMatchGetPaths :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> m [Text]
settingMatchGetPaths a
setting = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr Word32
length_ <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr CString
result <- Ptr SettingMatch -> Ptr Word32 -> IO (Ptr CString)
nm_setting_match_get_paths Ptr SettingMatch
setting' Ptr Word32
length_
Word32
length_' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
length_
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingMatchGetPaths" Ptr CString
result
[Text]
result' <- (Word32 -> Ptr CString -> IO [Text]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [Text]
unpackUTF8CArrayWithLength Word32
length_') Ptr CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
length_
[Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchGetPathsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchGetPathsMethodInfo a signature where
overloadedMethod = settingMatchGetPaths
instance O.OverloadedMethodInfo SettingMatchGetPathsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchGetPaths",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchGetPaths"
})
#endif
foreign import ccall "nm_setting_match_remove_driver" nm_setting_match_remove_driver ::
Ptr SettingMatch ->
Word32 ->
IO ()
settingMatchRemoveDriver ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Word32
-> m ()
settingMatchRemoveDriver :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Word32 -> m ()
settingMatchRemoveDriver a
setting Word32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> Word32 -> IO ()
nm_setting_match_remove_driver Ptr SettingMatch
setting' Word32
idx
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemoveDriverMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemoveDriverMethodInfo a signature where
overloadedMethod = settingMatchRemoveDriver
instance O.OverloadedMethodInfo SettingMatchRemoveDriverMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemoveDriver",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemoveDriver"
})
#endif
foreign import ccall "nm_setting_match_remove_driver_by_value" nm_setting_match_remove_driver_by_value ::
Ptr SettingMatch ->
CString ->
IO CInt
settingMatchRemoveDriverByValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m Bool
settingMatchRemoveDriverByValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m Bool
settingMatchRemoveDriverByValue a
setting Text
driver = 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
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
driver' <- Text -> IO CString
textToCString Text
driver
CInt
result <- Ptr SettingMatch -> CString -> IO CInt
nm_setting_match_remove_driver_by_value Ptr SettingMatch
setting' CString
driver'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
driver'
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemoveDriverByValueMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemoveDriverByValueMethodInfo a signature where
overloadedMethod = settingMatchRemoveDriverByValue
instance O.OverloadedMethodInfo SettingMatchRemoveDriverByValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemoveDriverByValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemoveDriverByValue"
})
#endif
foreign import ccall "nm_setting_match_remove_interface_name" nm_setting_match_remove_interface_name ::
Ptr SettingMatch ->
Int32 ->
IO ()
settingMatchRemoveInterfaceName ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Int32
-> m ()
settingMatchRemoveInterfaceName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Int32 -> m ()
settingMatchRemoveInterfaceName a
setting Int32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> Int32 -> IO ()
nm_setting_match_remove_interface_name Ptr SettingMatch
setting' Int32
idx
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemoveInterfaceNameMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemoveInterfaceNameMethodInfo a signature where
overloadedMethod = settingMatchRemoveInterfaceName
instance O.OverloadedMethodInfo SettingMatchRemoveInterfaceNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemoveInterfaceName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemoveInterfaceName"
})
#endif
foreign import ccall "nm_setting_match_remove_interface_name_by_value" nm_setting_match_remove_interface_name_by_value ::
Ptr SettingMatch ->
CString ->
IO CInt
settingMatchRemoveInterfaceNameByValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m Bool
settingMatchRemoveInterfaceNameByValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m Bool
settingMatchRemoveInterfaceNameByValue a
setting Text
interfaceName = 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
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
interfaceName' <- Text -> IO CString
textToCString Text
interfaceName
CInt
result <- Ptr SettingMatch -> CString -> IO CInt
nm_setting_match_remove_interface_name_by_value Ptr SettingMatch
setting' CString
interfaceName'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interfaceName'
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemoveInterfaceNameByValueMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemoveInterfaceNameByValueMethodInfo a signature where
overloadedMethod = settingMatchRemoveInterfaceNameByValue
instance O.OverloadedMethodInfo SettingMatchRemoveInterfaceNameByValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemoveInterfaceNameByValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemoveInterfaceNameByValue"
})
#endif
foreign import ccall "nm_setting_match_remove_kernel_command_line" nm_setting_match_remove_kernel_command_line ::
Ptr SettingMatch ->
Word32 ->
IO ()
settingMatchRemoveKernelCommandLine ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Word32
-> m ()
settingMatchRemoveKernelCommandLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Word32 -> m ()
settingMatchRemoveKernelCommandLine a
setting Word32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> Word32 -> IO ()
nm_setting_match_remove_kernel_command_line Ptr SettingMatch
setting' Word32
idx
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemoveKernelCommandLineMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemoveKernelCommandLineMethodInfo a signature where
overloadedMethod = settingMatchRemoveKernelCommandLine
instance O.OverloadedMethodInfo SettingMatchRemoveKernelCommandLineMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemoveKernelCommandLine",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemoveKernelCommandLine"
})
#endif
foreign import ccall "nm_setting_match_remove_kernel_command_line_by_value" nm_setting_match_remove_kernel_command_line_by_value ::
Ptr SettingMatch ->
CString ->
IO CInt
settingMatchRemoveKernelCommandLineByValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m Bool
settingMatchRemoveKernelCommandLineByValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m Bool
settingMatchRemoveKernelCommandLineByValue a
setting Text
kernelCommandLine = 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
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
kernelCommandLine' <- Text -> IO CString
textToCString Text
kernelCommandLine
CInt
result <- Ptr SettingMatch -> CString -> IO CInt
nm_setting_match_remove_kernel_command_line_by_value Ptr SettingMatch
setting' CString
kernelCommandLine'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
kernelCommandLine'
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemoveKernelCommandLineByValueMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemoveKernelCommandLineByValueMethodInfo a signature where
overloadedMethod = settingMatchRemoveKernelCommandLineByValue
instance O.OverloadedMethodInfo SettingMatchRemoveKernelCommandLineByValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemoveKernelCommandLineByValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemoveKernelCommandLineByValue"
})
#endif
foreign import ccall "nm_setting_match_remove_path" nm_setting_match_remove_path ::
Ptr SettingMatch ->
Word32 ->
IO ()
settingMatchRemovePath ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> Word32
-> m ()
settingMatchRemovePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Word32 -> m ()
settingMatchRemovePath a
setting Word32
idx = 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 SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
Ptr SettingMatch -> Word32 -> IO ()
nm_setting_match_remove_path Ptr SettingMatch
setting' Word32
idx
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemovePathMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemovePathMethodInfo a signature where
overloadedMethod = settingMatchRemovePath
instance O.OverloadedMethodInfo SettingMatchRemovePathMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemovePath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemovePath"
})
#endif
foreign import ccall "nm_setting_match_remove_path_by_value" nm_setting_match_remove_path_by_value ::
Ptr SettingMatch ->
CString ->
IO CInt
settingMatchRemovePathByValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingMatch a) =>
a
-> T.Text
-> m Bool
settingMatchRemovePathByValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingMatch a) =>
a -> Text -> m Bool
settingMatchRemovePathByValue a
setting Text
path = 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
Ptr SettingMatch
setting' <- a -> IO (Ptr SettingMatch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
CString
path' <- Text -> IO CString
textToCString Text
path
CInt
result <- Ptr SettingMatch -> CString -> IO CInt
nm_setting_match_remove_path_by_value Ptr SettingMatch
setting' CString
path'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SettingMatchRemovePathByValueMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsSettingMatch a) => O.OverloadedMethod SettingMatchRemovePathByValueMethodInfo a signature where
overloadedMethod = settingMatchRemovePathByValue
instance O.OverloadedMethodInfo SettingMatchRemovePathByValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.NM.Objects.SettingMatch.settingMatchRemovePathByValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingMatch.html#v:settingMatchRemovePathByValue"
})
#endif