{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.GLib.Structs.MappedFile.MappedFile' represents a file mapping created with
-- 'GI.GLib.Structs.MappedFile.mappedFileNew'. It has only private members and should
-- not be accessed directly.

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

module GI.GLib.Structs.MappedFile
    ( 

-- * Exported types
    MappedFile(..)                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [free]("GI.GLib.Structs.MappedFile#g:method:free"), [ref]("GI.GLib.Structs.MappedFile#g:method:ref"), [unref]("GI.GLib.Structs.MappedFile#g:method:unref").
-- 
-- ==== Getters
-- [getBytes]("GI.GLib.Structs.MappedFile#g:method:getBytes"), [getContents]("GI.GLib.Structs.MappedFile#g:method:getContents"), [getLength]("GI.GLib.Structs.MappedFile#g:method:getLength").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveMappedFileMethod                 ,
#endif

-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    MappedFileFreeMethodInfo                ,
#endif
    mappedFileFree                          ,


-- ** getBytes #method:getBytes#

#if defined(ENABLE_OVERLOADING)
    MappedFileGetBytesMethodInfo            ,
#endif
    mappedFileGetBytes                      ,


-- ** getContents #method:getContents#

#if defined(ENABLE_OVERLOADING)
    MappedFileGetContentsMethodInfo         ,
#endif
    mappedFileGetContents                   ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    MappedFileGetLengthMethodInfo           ,
#endif
    mappedFileGetLength                     ,


-- ** new #method:new#

    mappedFileNew                           ,


-- ** newFromFd #method:newFromFd#

    mappedFileNewFromFd                     ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    MappedFileRefMethodInfo                 ,
#endif
    mappedFileRef                           ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    MappedFileUnrefMethodInfo               ,
#endif
    mappedFileUnref                         ,




    ) 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.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.GLib.Structs.Bytes as GLib.Bytes

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

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

foreign import ccall "g_mapped_file_get_type" c_g_mapped_file_get_type :: 
    IO GType

type instance O.ParentTypes MappedFile = '[]
instance O.HasParentTypes MappedFile

instance B.Types.TypedObject MappedFile where
    glibType :: IO GType
glibType = IO GType
c_g_mapped_file_get_type

instance B.Types.GBoxed MappedFile

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


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MappedFile
type instance O.AttributeList MappedFile = MappedFileAttributeList
type MappedFileAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method MappedFile::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The path of the file to load, in the GLib\n    filename encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "writable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the mapping should be writable"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "MappedFile" })
-- throws : True
-- Skip return : False

foreign import ccall "g_mapped_file_new" g_mapped_file_new :: 
    CString ->                              -- filename : TBasicType TFileName
    CInt ->                                 -- writable : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr MappedFile)

-- | Maps a file into memory. On UNIX, this is using the @/mmap()/@ function.
-- 
-- If /@writable@/ is 'P.True', the mapped buffer may be modified, otherwise
-- it is an error to modify the mapped buffer. Modifications to the buffer
-- are not visible to other processes mapping the same file, and are not
-- written back to the file.
-- 
-- Note that modifications of the underlying file might affect the contents
-- of the t'GI.GLib.Structs.MappedFile.MappedFile'. Therefore, mapping should only be used if the file
-- will not be modified, or if all modifications of the file are done
-- atomically (e.g. using 'GI.GLib.Functions.fileSetContents').
-- 
-- If /@filename@/ is the name of an empty, regular file, the function
-- will successfully return an empty t'GI.GLib.Structs.MappedFile.MappedFile'. In other cases of
-- size 0 (e.g. device files such as \/dev\/null), /@error@/ will be set
-- to the t'GI.GLib.Enums.FileError' value @/G_FILE_ERROR_INVAL/@.
-- 
-- /Since: 2.8/
mappedFileNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: The path of the file to load, in the GLib
    --     filename encoding
    -> Bool
    -- ^ /@writable@/: whether the mapping should be writable
    -> m MappedFile
    -- ^ __Returns:__ a newly allocated t'GI.GLib.Structs.MappedFile.MappedFile' which must be unref\'d
    --    with 'GI.GLib.Structs.MappedFile.mappedFileUnref', or 'P.Nothing' if the mapping failed. /(Can throw 'Data.GI.Base.GError.GError')/
mappedFileNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[Char] -> Bool -> m MappedFile
mappedFileNew [Char]
filename Bool
writable = IO MappedFile -> m MappedFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MappedFile -> m MappedFile) -> IO MappedFile -> m MappedFile
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- [Char] -> IO CString
stringToCString [Char]
filename
    let writable' :: CInt
writable' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
writable
    IO MappedFile -> IO () -> IO MappedFile
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr MappedFile
result <- (Ptr (Ptr GError) -> IO (Ptr MappedFile)) -> IO (Ptr MappedFile)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr MappedFile)) -> IO (Ptr MappedFile))
-> (Ptr (Ptr GError) -> IO (Ptr MappedFile)) -> IO (Ptr MappedFile)
forall a b. (a -> b) -> a -> b
$ CString -> CInt -> Ptr (Ptr GError) -> IO (Ptr MappedFile)
g_mapped_file_new CString
filename' CInt
writable'
        Text -> Ptr MappedFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mappedFileNew" Ptr MappedFile
result
        MappedFile
result' <- ((ManagedPtr MappedFile -> MappedFile)
-> Ptr MappedFile -> IO MappedFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr MappedFile -> MappedFile
MappedFile) Ptr MappedFile
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        MappedFile -> IO MappedFile
forall (m :: * -> *) a. Monad m => a -> m a
return MappedFile
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method MappedFile::new_from_fd
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The file descriptor of the file to load"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "writable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the mapping should be writable"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "MappedFile" })
-- throws : True
-- Skip return : False

foreign import ccall "g_mapped_file_new_from_fd" g_mapped_file_new_from_fd :: 
    Int32 ->                                -- fd : TBasicType TInt
    CInt ->                                 -- writable : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr MappedFile)

-- | Maps a file into memory. On UNIX, this is using the @/mmap()/@ function.
-- 
-- If /@writable@/ is 'P.True', the mapped buffer may be modified, otherwise
-- it is an error to modify the mapped buffer. Modifications to the buffer
-- are not visible to other processes mapping the same file, and are not
-- written back to the file.
-- 
-- Note that modifications of the underlying file might affect the contents
-- of the t'GI.GLib.Structs.MappedFile.MappedFile'. Therefore, mapping should only be used if the file
-- will not be modified, or if all modifications of the file are done
-- atomically (e.g. using 'GI.GLib.Functions.fileSetContents').
-- 
-- /Since: 2.32/
mappedFileNewFromFd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@fd@/: The file descriptor of the file to load
    -> Bool
    -- ^ /@writable@/: whether the mapping should be writable
    -> m MappedFile
    -- ^ __Returns:__ a newly allocated t'GI.GLib.Structs.MappedFile.MappedFile' which must be unref\'d
    --    with 'GI.GLib.Structs.MappedFile.mappedFileUnref', or 'P.Nothing' if the mapping failed. /(Can throw 'Data.GI.Base.GError.GError')/
mappedFileNewFromFd :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int32 -> Bool -> m MappedFile
mappedFileNewFromFd Int32
fd Bool
writable = IO MappedFile -> m MappedFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MappedFile -> m MappedFile) -> IO MappedFile -> m MappedFile
forall a b. (a -> b) -> a -> b
$ do
    let writable' :: CInt
writable' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
writable
    IO MappedFile -> IO () -> IO MappedFile
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr MappedFile
result <- (Ptr (Ptr GError) -> IO (Ptr MappedFile)) -> IO (Ptr MappedFile)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr MappedFile)) -> IO (Ptr MappedFile))
-> (Ptr (Ptr GError) -> IO (Ptr MappedFile)) -> IO (Ptr MappedFile)
forall a b. (a -> b) -> a -> b
$ Int32 -> CInt -> Ptr (Ptr GError) -> IO (Ptr MappedFile)
g_mapped_file_new_from_fd Int32
fd CInt
writable'
        Text -> Ptr MappedFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mappedFileNewFromFd" Ptr MappedFile
result
        MappedFile
result' <- ((ManagedPtr MappedFile -> MappedFile)
-> Ptr MappedFile -> IO MappedFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr MappedFile -> MappedFile
MappedFile) Ptr MappedFile
result
        MappedFile -> IO MappedFile
forall (m :: * -> *) a. Monad m => a -> m a
return MappedFile
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method MappedFile::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MappedFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMappedFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mapped_file_free" g_mapped_file_free :: 
    Ptr MappedFile ->                       -- file : TInterface (Name {namespace = "GLib", name = "MappedFile"})
    IO ()

{-# DEPRECATED mappedFileFree ["(Since version 2.22)","Use 'GI.GLib.Structs.MappedFile.mappedFileUnref' instead."] #-}
-- | This call existed before t'GI.GLib.Structs.MappedFile.MappedFile' had refcounting and is currently
-- exactly the same as 'GI.GLib.Structs.MappedFile.mappedFileUnref'.
-- 
-- /Since: 2.8/
mappedFileFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MappedFile
    -- ^ /@file@/: a t'GI.GLib.Structs.MappedFile.MappedFile'
    -> m ()
mappedFileFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MappedFile -> m ()
mappedFileFree MappedFile
file = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MappedFile
file' <- MappedFile -> IO (Ptr MappedFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MappedFile
file
    Ptr MappedFile -> IO ()
g_mapped_file_free Ptr MappedFile
file'
    MappedFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MappedFile
file
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MappedFileFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MappedFileFreeMethodInfo MappedFile signature where
    overloadedMethod = mappedFileFree

instance O.OverloadedMethodInfo MappedFileFreeMethodInfo MappedFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MappedFile.mappedFileFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-MappedFile.html#v:mappedFileFree"
        })


#endif

-- method MappedFile::get_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MappedFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMappedFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "g_mapped_file_get_bytes" g_mapped_file_get_bytes :: 
    Ptr MappedFile ->                       -- file : TInterface (Name {namespace = "GLib", name = "MappedFile"})
    IO (Ptr GLib.Bytes.Bytes)

-- | Creates a new t'GI.GLib.Structs.Bytes.Bytes' which references the data mapped from /@file@/.
-- The mapped contents of the file must not be modified after creating this
-- bytes object, because a t'GI.GLib.Structs.Bytes.Bytes' should be immutable.
-- 
-- /Since: 2.34/
mappedFileGetBytes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MappedFile
    -- ^ /@file@/: a t'GI.GLib.Structs.MappedFile.MappedFile'
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ A newly allocated t'GI.GLib.Structs.Bytes.Bytes' referencing data
    --     from /@file@/
mappedFileGetBytes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MappedFile -> m Bytes
mappedFileGetBytes MappedFile
file = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
    Ptr MappedFile
file' <- MappedFile -> IO (Ptr MappedFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MappedFile
file
    Ptr Bytes
result <- Ptr MappedFile -> IO (Ptr Bytes)
g_mapped_file_get_bytes Ptr MappedFile
file'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mappedFileGetBytes" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    MappedFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MappedFile
file
    Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
data MappedFileGetBytesMethodInfo
instance (signature ~ (m GLib.Bytes.Bytes), MonadIO m) => O.OverloadedMethod MappedFileGetBytesMethodInfo MappedFile signature where
    overloadedMethod = mappedFileGetBytes

instance O.OverloadedMethodInfo MappedFileGetBytesMethodInfo MappedFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MappedFile.mappedFileGetBytes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-MappedFile.html#v:mappedFileGetBytes"
        })


#endif

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

foreign import ccall "g_mapped_file_get_contents" g_mapped_file_get_contents :: 
    Ptr MappedFile ->                       -- file : TInterface (Name {namespace = "GLib", name = "MappedFile"})
    IO CString

-- | Returns the contents of a t'GI.GLib.Structs.MappedFile.MappedFile'.
-- 
-- Note that the contents may not be zero-terminated,
-- even if the t'GI.GLib.Structs.MappedFile.MappedFile' is backed by a text file.
-- 
-- If the file is empty then 'P.Nothing' is returned.
-- 
-- /Since: 2.8/
mappedFileGetContents ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MappedFile
    -- ^ /@file@/: a t'GI.GLib.Structs.MappedFile.MappedFile'
    -> m T.Text
    -- ^ __Returns:__ the contents of /@file@/, or 'P.Nothing'.
mappedFileGetContents :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MappedFile -> m Text
mappedFileGetContents MappedFile
file = IO Text -> m Text
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 MappedFile
file' <- MappedFile -> IO (Ptr MappedFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MappedFile
file
    CString
result <- Ptr MappedFile -> IO CString
g_mapped_file_get_contents Ptr MappedFile
file'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mappedFileGetContents" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    MappedFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MappedFile
file
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MappedFileGetContentsMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod MappedFileGetContentsMethodInfo MappedFile signature where
    overloadedMethod = mappedFileGetContents

instance O.OverloadedMethodInfo MappedFileGetContentsMethodInfo MappedFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MappedFile.mappedFileGetContents",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-MappedFile.html#v:mappedFileGetContents"
        })


#endif

-- method MappedFile::get_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MappedFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMappedFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_mapped_file_get_length" g_mapped_file_get_length :: 
    Ptr MappedFile ->                       -- file : TInterface (Name {namespace = "GLib", name = "MappedFile"})
    IO Word64

-- | Returns the length of the contents of a t'GI.GLib.Structs.MappedFile.MappedFile'.
-- 
-- /Since: 2.8/
mappedFileGetLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MappedFile
    -- ^ /@file@/: a t'GI.GLib.Structs.MappedFile.MappedFile'
    -> m Word64
    -- ^ __Returns:__ the length of the contents of /@file@/.
mappedFileGetLength :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MappedFile -> m Word64
mappedFileGetLength MappedFile
file = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr MappedFile
file' <- MappedFile -> IO (Ptr MappedFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MappedFile
file
    Word64
result <- Ptr MappedFile -> IO Word64
g_mapped_file_get_length Ptr MappedFile
file'
    MappedFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MappedFile
file
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data MappedFileGetLengthMethodInfo
instance (signature ~ (m Word64), MonadIO m) => O.OverloadedMethod MappedFileGetLengthMethodInfo MappedFile signature where
    overloadedMethod = mappedFileGetLength

instance O.OverloadedMethodInfo MappedFileGetLengthMethodInfo MappedFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MappedFile.mappedFileGetLength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-MappedFile.html#v:mappedFileGetLength"
        })


#endif

-- method MappedFile::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MappedFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMappedFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "MappedFile" })
-- throws : False
-- Skip return : False

foreign import ccall "g_mapped_file_ref" g_mapped_file_ref :: 
    Ptr MappedFile ->                       -- file : TInterface (Name {namespace = "GLib", name = "MappedFile"})
    IO (Ptr MappedFile)

-- | Increments the reference count of /@file@/ by one.  It is safe to call
-- this function from any thread.
-- 
-- /Since: 2.22/
mappedFileRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MappedFile
    -- ^ /@file@/: a t'GI.GLib.Structs.MappedFile.MappedFile'
    -> m MappedFile
    -- ^ __Returns:__ the passed in t'GI.GLib.Structs.MappedFile.MappedFile'.
mappedFileRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MappedFile -> m MappedFile
mappedFileRef MappedFile
file = IO MappedFile -> m MappedFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MappedFile -> m MappedFile) -> IO MappedFile -> m MappedFile
forall a b. (a -> b) -> a -> b
$ do
    Ptr MappedFile
file' <- MappedFile -> IO (Ptr MappedFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MappedFile
file
    Ptr MappedFile
result <- Ptr MappedFile -> IO (Ptr MappedFile)
g_mapped_file_ref Ptr MappedFile
file'
    Text -> Ptr MappedFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mappedFileRef" Ptr MappedFile
result
    MappedFile
result' <- ((ManagedPtr MappedFile -> MappedFile)
-> Ptr MappedFile -> IO MappedFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr MappedFile -> MappedFile
MappedFile) Ptr MappedFile
result
    MappedFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MappedFile
file
    MappedFile -> IO MappedFile
forall (m :: * -> *) a. Monad m => a -> m a
return MappedFile
result'

#if defined(ENABLE_OVERLOADING)
data MappedFileRefMethodInfo
instance (signature ~ (m MappedFile), MonadIO m) => O.OverloadedMethod MappedFileRefMethodInfo MappedFile signature where
    overloadedMethod = mappedFileRef

instance O.OverloadedMethodInfo MappedFileRefMethodInfo MappedFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MappedFile.mappedFileRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-MappedFile.html#v:mappedFileRef"
        })


#endif

-- method MappedFile::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MappedFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMappedFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mapped_file_unref" g_mapped_file_unref :: 
    Ptr MappedFile ->                       -- file : TInterface (Name {namespace = "GLib", name = "MappedFile"})
    IO ()

-- | Decrements the reference count of /@file@/ by one.  If the reference count
-- drops to 0, unmaps the buffer of /@file@/ and frees it.
-- 
-- It is safe to call this function from any thread.
-- 
-- Since 2.22
mappedFileUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MappedFile
    -- ^ /@file@/: a t'GI.GLib.Structs.MappedFile.MappedFile'
    -> m ()
mappedFileUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MappedFile -> m ()
mappedFileUnref MappedFile
file = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MappedFile
file' <- MappedFile -> IO (Ptr MappedFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MappedFile
file
    Ptr MappedFile -> IO ()
g_mapped_file_unref Ptr MappedFile
file'
    MappedFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MappedFile
file
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MappedFileUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MappedFileUnrefMethodInfo MappedFile signature where
    overloadedMethod = mappedFileUnref

instance O.OverloadedMethodInfo MappedFileUnrefMethodInfo MappedFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MappedFile.mappedFileUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-MappedFile.html#v:mappedFileUnref"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveMappedFileMethod (t :: Symbol) (o :: *) :: * where
    ResolveMappedFileMethod "free" o = MappedFileFreeMethodInfo
    ResolveMappedFileMethod "ref" o = MappedFileRefMethodInfo
    ResolveMappedFileMethod "unref" o = MappedFileUnrefMethodInfo
    ResolveMappedFileMethod "getBytes" o = MappedFileGetBytesMethodInfo
    ResolveMappedFileMethod "getContents" o = MappedFileGetContentsMethodInfo
    ResolveMappedFileMethod "getLength" o = MappedFileGetLengthMethodInfo
    ResolveMappedFileMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif