{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.Path
(
Path(..) ,
IsPath ,
toPath ,
#if defined(ENABLE_OVERLOADING)
ResolvePathMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PathAppendMethodInfo ,
#endif
pathAppend ,
#if defined(ENABLE_OVERLOADING)
PathGetElementMethodInfo ,
#endif
pathGetElement ,
#if defined(ENABLE_OVERLOADING)
PathGetElementsMethodInfo ,
#endif
pathGetElements ,
#if defined(ENABLE_OVERLOADING)
PathGetLengthMethodInfo ,
#endif
pathGetLength ,
#if defined(ENABLE_OVERLOADING)
PathHasPrefixMethodInfo ,
#endif
pathHasPrefix ,
#if defined(ENABLE_OVERLOADING)
PathIsEmptyMethodInfo ,
#endif
pathIsEmpty ,
pathNew ,
#if defined(ENABLE_OVERLOADING)
PathPrependMethodInfo ,
#endif
pathPrepend ,
#if defined(ENABLE_OVERLOADING)
PathPrintfMethodInfo ,
#endif
pathPrintf ,
) 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 {-# SOURCE #-} qualified GI.Dazzle.Objects.PathElement as Dazzle.PathElement
import qualified GI.GObject.Objects.Object as GObject.Object
#else
import {-# SOURCE #-} qualified GI.Dazzle.Objects.PathElement as Dazzle.PathElement
import qualified GI.GObject.Objects.Object as GObject.Object
#endif
newtype Path = Path (SP.ManagedPtr Path)
deriving (Path -> Path -> Bool
(Path -> Path -> Bool) -> (Path -> Path -> Bool) -> Eq Path
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Path -> Path -> Bool
== :: Path -> Path -> Bool
$c/= :: Path -> Path -> Bool
/= :: Path -> Path -> Bool
Eq)
instance SP.ManagedPtrNewtype Path where
toManagedPtr :: Path -> ManagedPtr Path
toManagedPtr (Path ManagedPtr Path
p) = ManagedPtr Path
p
foreign import ccall "dzl_path_get_type"
c_dzl_path_get_type :: IO B.Types.GType
instance B.Types.TypedObject Path where
glibType :: IO GType
glibType = IO GType
c_dzl_path_get_type
instance B.Types.GObject Path
class (SP.GObject o, O.IsDescendantOf Path o) => IsPath o
instance (SP.GObject o, O.IsDescendantOf Path o) => IsPath o
instance O.HasParentTypes Path
type instance O.ParentTypes Path = '[GObject.Object.Object]
toPath :: (MIO.MonadIO m, IsPath o) => o -> m Path
toPath :: forall (m :: * -> *) o. (MonadIO m, IsPath o) => o -> m Path
toPath = IO Path -> m Path
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Path -> m Path) -> (o -> IO Path) -> o -> m Path
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Path -> Path) -> o -> IO Path
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Path -> Path
Path
instance B.GValue.IsGValue (Maybe Path) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_path_get_type
gvalueSet_ :: Ptr GValue -> Maybe Path -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Path
P.Nothing = Ptr GValue -> Ptr Path -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Path
forall a. Ptr a
FP.nullPtr :: FP.Ptr Path)
gvalueSet_ Ptr GValue
gv (P.Just Path
obj) = Path -> (Ptr Path -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Path
obj (Ptr GValue -> Ptr Path -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Path)
gvalueGet_ Ptr GValue
gv = do
Ptr Path
ptr <- Ptr GValue -> IO (Ptr Path)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Path)
if Ptr Path
ptr Ptr Path -> Ptr Path -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Path
forall a. Ptr a
FP.nullPtr
then Path -> Maybe Path
forall a. a -> Maybe a
P.Just (Path -> Maybe Path) -> IO Path -> IO (Maybe Path)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Path -> Path) -> Ptr Path -> IO Path
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Path -> Path
Path Ptr Path
ptr
else Maybe Path -> IO (Maybe Path)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Path
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolvePathMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePathMethod "append" o = PathAppendMethodInfo
ResolvePathMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolvePathMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolvePathMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolvePathMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolvePathMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolvePathMethod "hasPrefix" o = PathHasPrefixMethodInfo
ResolvePathMethod "isEmpty" o = PathIsEmptyMethodInfo
ResolvePathMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolvePathMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolvePathMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolvePathMethod "prepend" o = PathPrependMethodInfo
ResolvePathMethod "printf" o = PathPrintfMethodInfo
ResolvePathMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolvePathMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolvePathMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolvePathMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolvePathMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolvePathMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolvePathMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolvePathMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolvePathMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolvePathMethod "getElement" o = PathGetElementMethodInfo
ResolvePathMethod "getElements" o = PathGetElementsMethodInfo
ResolvePathMethod "getLength" o = PathGetLengthMethodInfo
ResolvePathMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolvePathMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolvePathMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolvePathMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolvePathMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolvePathMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePathMethod t Path, O.OverloadedMethod info Path p) => OL.IsLabel t (Path -> 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 ~ ResolvePathMethod t Path, O.OverloadedMethod info Path p, R.HasField t Path p) => R.HasField t Path p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePathMethod t Path, O.OverloadedMethodInfo info Path) => OL.IsLabel t (O.MethodProxy info Path) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Path
type instance O.AttributeList Path = PathAttributeList
type PathAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Path = PathSignalList
type PathSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_path_new" dzl_path_new ::
IO (Ptr Path)
pathNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Path
pathNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Path
pathNew = IO Path -> m Path
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Path -> m Path) -> IO Path -> m Path
forall a b. (a -> b) -> a -> b
$ do
Ptr Path
result <- IO (Ptr Path)
dzl_path_new
Text -> Ptr Path -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pathNew" Ptr Path
result
Path
result' <- ((ManagedPtr Path -> Path) -> Ptr Path -> IO Path
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Path -> Path
Path) Ptr Path
result
Path -> IO Path
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Path
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_path_append" dzl_path_append ::
Ptr Path ->
Ptr Dazzle.PathElement.PathElement ->
IO ()
pathAppend ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a, Dazzle.PathElement.IsPathElement b) =>
a
-> b
-> m ()
pathAppend :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPath a, IsPathElement b) =>
a -> b -> m ()
pathAppend a
self b
element = 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 Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr PathElement
element' <- b -> IO (Ptr PathElement)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
element
Ptr Path -> Ptr PathElement -> IO ()
dzl_path_append Ptr Path
self' Ptr PathElement
element'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
element
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PathAppendMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPath a, Dazzle.PathElement.IsPathElement b) => O.OverloadedMethod PathAppendMethodInfo a signature where
overloadedMethod = pathAppend
instance O.OverloadedMethodInfo PathAppendMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathAppend",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathAppend"
})
#endif
foreign import ccall "dzl_path_get_element" dzl_path_get_element ::
Ptr Path ->
Word32 ->
IO (Ptr Dazzle.PathElement.PathElement)
pathGetElement ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a) =>
a
-> Word32
-> m (Maybe Dazzle.PathElement.PathElement)
pathGetElement :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPath a) =>
a -> Word32 -> m (Maybe PathElement)
pathGetElement a
self Word32
index = IO (Maybe PathElement) -> m (Maybe PathElement)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PathElement) -> m (Maybe PathElement))
-> IO (Maybe PathElement) -> m (Maybe PathElement)
forall a b. (a -> b) -> a -> b
$ do
Ptr Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr PathElement
result <- Ptr Path -> Word32 -> IO (Ptr PathElement)
dzl_path_get_element Ptr Path
self' Word32
index
Maybe PathElement
maybeResult <- Ptr PathElement
-> (Ptr PathElement -> IO PathElement) -> IO (Maybe PathElement)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PathElement
result ((Ptr PathElement -> IO PathElement) -> IO (Maybe PathElement))
-> (Ptr PathElement -> IO PathElement) -> IO (Maybe PathElement)
forall a b. (a -> b) -> a -> b
$ \Ptr PathElement
result' -> do
PathElement
result'' <- ((ManagedPtr PathElement -> PathElement)
-> Ptr PathElement -> IO PathElement
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PathElement -> PathElement
Dazzle.PathElement.PathElement) Ptr PathElement
result'
PathElement -> IO PathElement
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PathElement
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe PathElement -> IO (Maybe PathElement)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PathElement
maybeResult
#if defined(ENABLE_OVERLOADING)
data PathGetElementMethodInfo
instance (signature ~ (Word32 -> m (Maybe Dazzle.PathElement.PathElement)), MonadIO m, IsPath a) => O.OverloadedMethod PathGetElementMethodInfo a signature where
overloadedMethod = pathGetElement
instance O.OverloadedMethodInfo PathGetElementMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathGetElement",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathGetElement"
})
#endif
foreign import ccall "dzl_path_get_elements" dzl_path_get_elements ::
Ptr Path ->
IO (Ptr (GList (Ptr Dazzle.PathElement.PathElement)))
pathGetElements ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a) =>
a
-> m [Dazzle.PathElement.PathElement]
pathGetElements :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPath a) =>
a -> m [PathElement]
pathGetElements a
self = IO [PathElement] -> m [PathElement]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [PathElement] -> m [PathElement])
-> IO [PathElement] -> m [PathElement]
forall a b. (a -> b) -> a -> b
$ do
Ptr Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr (GList (Ptr PathElement))
result <- Ptr Path -> IO (Ptr (GList (Ptr PathElement)))
dzl_path_get_elements Ptr Path
self'
[Ptr PathElement]
result' <- Ptr (GList (Ptr PathElement)) -> IO [Ptr PathElement]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr PathElement))
result
[PathElement]
result'' <- (Ptr PathElement -> IO PathElement)
-> [Ptr PathElement] -> IO [PathElement]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr PathElement -> PathElement)
-> Ptr PathElement -> IO PathElement
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PathElement -> PathElement
Dazzle.PathElement.PathElement) [Ptr PathElement]
result'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
[PathElement] -> IO [PathElement]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [PathElement]
result''
#if defined(ENABLE_OVERLOADING)
data PathGetElementsMethodInfo
instance (signature ~ (m [Dazzle.PathElement.PathElement]), MonadIO m, IsPath a) => O.OverloadedMethod PathGetElementsMethodInfo a signature where
overloadedMethod = pathGetElements
instance O.OverloadedMethodInfo PathGetElementsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathGetElements",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathGetElements"
})
#endif
foreign import ccall "dzl_path_get_length" dzl_path_get_length ::
Ptr Path ->
IO Word32
pathGetLength ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a) =>
a
-> m Word32
pathGetLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPath a) =>
a -> m Word32
pathGetLength a
self = 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 Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Word32
result <- Ptr Path -> IO Word32
dzl_path_get_length Ptr Path
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data PathGetLengthMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsPath a) => O.OverloadedMethod PathGetLengthMethodInfo a signature where
overloadedMethod = pathGetLength
instance O.OverloadedMethodInfo PathGetLengthMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathGetLength",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathGetLength"
})
#endif
foreign import ccall "dzl_path_has_prefix" dzl_path_has_prefix ::
Ptr Path ->
Ptr Path ->
IO CInt
pathHasPrefix ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a, IsPath b) =>
a
-> b
-> m Bool
pathHasPrefix :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPath a, IsPath b) =>
a -> b -> m Bool
pathHasPrefix a
self b
prefix = 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 Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Path
prefix' <- b -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
prefix
CInt
result <- Ptr Path -> Ptr Path -> IO CInt
dzl_path_has_prefix Ptr Path
self' Ptr Path
prefix'
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
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
prefix
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PathHasPrefixMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsPath a, IsPath b) => O.OverloadedMethod PathHasPrefixMethodInfo a signature where
overloadedMethod = pathHasPrefix
instance O.OverloadedMethodInfo PathHasPrefixMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathHasPrefix",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathHasPrefix"
})
#endif
foreign import ccall "dzl_path_is_empty" dzl_path_is_empty ::
Ptr Path ->
IO CInt
pathIsEmpty ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a) =>
a
-> m Bool
pathIsEmpty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPath a) =>
a -> m Bool
pathIsEmpty a
self = 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 Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr Path -> IO CInt
dzl_path_is_empty Ptr Path
self'
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
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PathIsEmptyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPath a) => O.OverloadedMethod PathIsEmptyMethodInfo a signature where
overloadedMethod = pathIsEmpty
instance O.OverloadedMethodInfo PathIsEmptyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathIsEmpty",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathIsEmpty"
})
#endif
foreign import ccall "dzl_path_prepend" dzl_path_prepend ::
Ptr Path ->
Ptr Dazzle.PathElement.PathElement ->
IO ()
pathPrepend ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a, Dazzle.PathElement.IsPathElement b) =>
a
-> b
-> m ()
pathPrepend :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPath a, IsPathElement b) =>
a -> b -> m ()
pathPrepend a
self b
element = 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 Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr PathElement
element' <- b -> IO (Ptr PathElement)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
element
Ptr Path -> Ptr PathElement -> IO ()
dzl_path_prepend Ptr Path
self' Ptr PathElement
element'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
element
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PathPrependMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPath a, Dazzle.PathElement.IsPathElement b) => O.OverloadedMethod PathPrependMethodInfo a signature where
overloadedMethod = pathPrepend
instance O.OverloadedMethodInfo PathPrependMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathPrepend",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathPrepend"
})
#endif
foreign import ccall "dzl_path_printf" dzl_path_printf ::
Ptr Path ->
IO CString
pathPrintf ::
(B.CallStack.HasCallStack, MonadIO m, IsPath a) =>
a
-> m T.Text
pathPrintf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPath a) =>
a -> m Text
pathPrintf a
self = 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 Path
self' <- a -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr Path -> IO CString
dzl_path_printf Ptr Path
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pathPrintf" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data PathPrintfMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPath a) => O.OverloadedMethod PathPrintfMethodInfo a signature where
overloadedMethod = pathPrintf
instance O.OverloadedMethodInfo PathPrintfMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Path.pathPrintf",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Path.html#v:pathPrintf"
})
#endif