module System.Glib.GString (
GString,
readGString,
readGStringByteString,
fromGString,
) where
import Foreign
import Control.Exception (bracket)
import Control.Monad (foldM)
import Data.ByteString (ByteString, packCStringLen)
import System.Glib.FFI
type GString = Ptr (())
readGString :: GString -> IO (Maybe String)
readGString gstring
| gstring == nullPtr = return Nothing
| otherwise = do
gstr <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr CChar)}) gstring
len <- (\ptr -> do {peekByteOff ptr 8 ::IO CULong}) gstring
fmap Just $ peekCStringLen (gstr, fromIntegral len)
readGStringByteString :: GString -> IO (Maybe ByteString)
readGStringByteString gstring
| gstring == nullPtr = return Nothing
| otherwise = do
gstr <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr CChar)}) gstring
len <- (\ptr -> do {peekByteOff ptr 8 ::IO CULong}) gstring
fmap Just $ packCStringLen (gstr, fromIntegral len)
fromGString :: GString -> IO (Maybe String)
fromGString gstring
| gstring == nullPtr = return Nothing
| otherwise = do
gstr <- (\ptr -> do {peekByteOff ptr 0 ::IO (Ptr CChar)}) gstring
len <- (\ptr -> do {peekByteOff ptr 8 ::IO CULong}) gstring
str <- fmap Just $ peekCStringLen (gstr, fromIntegral len)
_ <- g_string_free gstring $ fromBool True
return str
foreign import ccall unsafe "g_string_free"
g_string_free :: ((Ptr ()) -> (CInt -> (IO (Ptr CChar))))