{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.Atom
(
Atom(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveAtomMethod ,
#endif
atomIntern ,
atomInternStaticString ,
#if defined(ENABLE_OVERLOADING)
AtomNameMethodInfo ,
#endif
atomName ,
) 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
newtype Atom = Atom (SP.ManagedPtr Atom)
deriving (Atom -> Atom -> Bool
(Atom -> Atom -> Bool) -> (Atom -> Atom -> Bool) -> Eq Atom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Atom -> Atom -> Bool
== :: Atom -> Atom -> Bool
$c/= :: Atom -> Atom -> Bool
/= :: Atom -> Atom -> Bool
Eq)
instance SP.ManagedPtrNewtype Atom where
toManagedPtr :: Atom -> ManagedPtr Atom
toManagedPtr (Atom ManagedPtr Atom
p) = ManagedPtr Atom
p
instance BoxedPtr Atom where
boxedPtrCopy :: Atom -> IO Atom
boxedPtrCopy = Atom -> IO Atom
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
boxedPtrFree :: Atom -> IO ()
boxedPtrFree = \Atom
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Atom
type instance O.AttributeList Atom = AtomAttributeList
type AtomAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_atom_name" gdk_atom_name ::
Ptr Atom ->
IO CString
atomName ::
(B.CallStack.HasCallStack, MonadIO m) =>
Atom
-> m T.Text
atomName :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Atom -> m Text
atomName Atom
atom = 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 Atom
atom' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
atom
CString
result <- Ptr Atom -> IO CString
gdk_atom_name Ptr Atom
atom'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"atomName" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
atom
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data AtomNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod AtomNameMethodInfo Atom signature where
overloadedMethod = atomName
instance O.OverloadedMethodInfo AtomNameMethodInfo Atom where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.Atom.atomName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.28/docs/GI-Gdk-Structs-Atom.html#v:atomName"
})
#endif
foreign import ccall "gdk_atom_intern" gdk_atom_intern ::
CString ->
CInt ->
IO (Ptr Atom)
atomIntern ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Bool
-> m Atom
atomIntern :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Bool -> m Atom
atomIntern Text
atomName Bool
onlyIfExists = IO Atom -> m Atom
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ do
CString
atomName' <- Text -> IO CString
textToCString Text
atomName
let onlyIfExists' :: CInt
onlyIfExists' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
onlyIfExists
Ptr Atom
result <- CString -> CInt -> IO (Ptr Atom)
gdk_atom_intern CString
atomName' CInt
onlyIfExists'
Text -> Ptr Atom -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"atomIntern" Ptr Atom
result
Atom
result' <- ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Atom) Ptr Atom
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
atomName'
Atom -> IO Atom
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_atom_intern_static_string" gdk_atom_intern_static_string ::
CString ->
IO (Ptr Atom)
atomInternStaticString ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m Atom
atomInternStaticString :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m Atom
atomInternStaticString Text
atomName = IO Atom -> m Atom
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ do
CString
atomName' <- Text -> IO CString
textToCString Text
atomName
Ptr Atom
result <- CString -> IO (Ptr Atom)
gdk_atom_intern_static_string CString
atomName'
Text -> Ptr Atom -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"atomInternStaticString" Ptr Atom
result
Atom
result' <- ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Atom) Ptr Atom
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
atomName'
Atom -> IO Atom
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAtomMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveAtomMethod "name" o = AtomNameMethodInfo
ResolveAtomMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAtomMethod t Atom, O.OverloadedMethod info Atom p) => OL.IsLabel t (Atom -> 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 ~ ResolveAtomMethod t Atom, O.OverloadedMethod info Atom p, R.HasField t Atom p) => R.HasField t Atom p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAtomMethod t Atom, O.OverloadedMethodInfo info Atom) => OL.IsLabel t (O.MethodProxy info Atom) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif