{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gio.Objects.DataInputStream
    ( 

-- * Exported types
    DataInputStream(..)                     ,
    DataInputStreamK                        ,
    toDataInputStream                       ,
    noDataInputStream                       ,


 -- * Methods
-- ** dataInputStreamGetByteOrder
    dataInputStreamGetByteOrder             ,


-- ** dataInputStreamGetNewlineType
    dataInputStreamGetNewlineType           ,


-- ** dataInputStreamNew
    dataInputStreamNew                      ,


-- ** dataInputStreamReadByte
    dataInputStreamReadByte                 ,


-- ** dataInputStreamReadInt16
    dataInputStreamReadInt16                ,


-- ** dataInputStreamReadInt32
    dataInputStreamReadInt32                ,


-- ** dataInputStreamReadInt64
    dataInputStreamReadInt64                ,


-- ** dataInputStreamReadLine
    dataInputStreamReadLine                 ,


-- ** dataInputStreamReadLineAsync
    dataInputStreamReadLineAsync            ,


-- ** dataInputStreamReadLineFinish
    dataInputStreamReadLineFinish           ,


-- ** dataInputStreamReadLineFinishUtf8
    dataInputStreamReadLineFinishUtf8       ,


-- ** dataInputStreamReadLineUtf8
    dataInputStreamReadLineUtf8             ,


-- ** dataInputStreamReadUint16
    dataInputStreamReadUint16               ,


-- ** dataInputStreamReadUint32
    dataInputStreamReadUint32               ,


-- ** dataInputStreamReadUint64
    dataInputStreamReadUint64               ,


-- ** dataInputStreamReadUntil
    dataInputStreamReadUntil                ,


-- ** dataInputStreamReadUntilAsync
    dataInputStreamReadUntilAsync           ,


-- ** dataInputStreamReadUntilFinish
    dataInputStreamReadUntilFinish          ,


-- ** dataInputStreamReadUpto
    dataInputStreamReadUpto                 ,


-- ** dataInputStreamReadUptoAsync
    dataInputStreamReadUptoAsync            ,


-- ** dataInputStreamReadUptoFinish
    dataInputStreamReadUptoFinish           ,


-- ** dataInputStreamSetByteOrder
    dataInputStreamSetByteOrder             ,


-- ** dataInputStreamSetNewlineType
    dataInputStreamSetNewlineType           ,




 -- * Properties
-- ** ByteOrder
    DataInputStreamByteOrderPropertyInfo    ,
    constructDataInputStreamByteOrder       ,
    getDataInputStreamByteOrder             ,
    setDataInputStreamByteOrder             ,


-- ** NewlineType
    DataInputStreamNewlineTypePropertyInfo  ,
    constructDataInputStreamNewlineType     ,
    getDataInputStreamNewlineType           ,
    setDataInputStreamNewlineType           ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gio.Types
import GI.Gio.Callbacks
import qualified GI.GObject as GObject

newtype DataInputStream = DataInputStream (ForeignPtr DataInputStream)
foreign import ccall "g_data_input_stream_get_type"
    c_g_data_input_stream_get_type :: IO GType

type instance ParentTypes DataInputStream = DataInputStreamParentTypes
type DataInputStreamParentTypes = '[BufferedInputStream, FilterInputStream, InputStream, GObject.Object, Seekable]

instance GObject DataInputStream where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_g_data_input_stream_get_type
    

class GObject o => DataInputStreamK o
instance (GObject o, IsDescendantOf DataInputStream o) => DataInputStreamK o

toDataInputStream :: DataInputStreamK o => o -> IO DataInputStream
toDataInputStream = unsafeCastTo DataInputStream

noDataInputStream :: Maybe DataInputStream
noDataInputStream = Nothing

-- VVV Prop "byte-order"
   -- Type: TInterface "Gio" "DataStreamByteOrder"
   -- Flags: [PropertyReadable,PropertyWritable]

getDataInputStreamByteOrder :: (MonadIO m, DataInputStreamK o) => o -> m DataStreamByteOrder
getDataInputStreamByteOrder obj = liftIO $ getObjectPropertyEnum obj "byte-order"

setDataInputStreamByteOrder :: (MonadIO m, DataInputStreamK o) => o -> DataStreamByteOrder -> m ()
setDataInputStreamByteOrder obj val = liftIO $ setObjectPropertyEnum obj "byte-order" val

constructDataInputStreamByteOrder :: DataStreamByteOrder -> IO ([Char], GValue)
constructDataInputStreamByteOrder val = constructObjectPropertyEnum "byte-order" val

data DataInputStreamByteOrderPropertyInfo
instance AttrInfo DataInputStreamByteOrderPropertyInfo where
    type AttrAllowedOps DataInputStreamByteOrderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DataInputStreamByteOrderPropertyInfo = (~) DataStreamByteOrder
    type AttrBaseTypeConstraint DataInputStreamByteOrderPropertyInfo = DataInputStreamK
    type AttrGetType DataInputStreamByteOrderPropertyInfo = DataStreamByteOrder
    type AttrLabel DataInputStreamByteOrderPropertyInfo = "DataInputStream::byte-order"
    attrGet _ = getDataInputStreamByteOrder
    attrSet _ = setDataInputStreamByteOrder
    attrConstruct _ = constructDataInputStreamByteOrder

-- VVV Prop "newline-type"
   -- Type: TInterface "Gio" "DataStreamNewlineType"
   -- Flags: [PropertyReadable,PropertyWritable]

getDataInputStreamNewlineType :: (MonadIO m, DataInputStreamK o) => o -> m DataStreamNewlineType
getDataInputStreamNewlineType obj = liftIO $ getObjectPropertyEnum obj "newline-type"

setDataInputStreamNewlineType :: (MonadIO m, DataInputStreamK o) => o -> DataStreamNewlineType -> m ()
setDataInputStreamNewlineType obj val = liftIO $ setObjectPropertyEnum obj "newline-type" val

constructDataInputStreamNewlineType :: DataStreamNewlineType -> IO ([Char], GValue)
constructDataInputStreamNewlineType val = constructObjectPropertyEnum "newline-type" val

data DataInputStreamNewlineTypePropertyInfo
instance AttrInfo DataInputStreamNewlineTypePropertyInfo where
    type AttrAllowedOps DataInputStreamNewlineTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint DataInputStreamNewlineTypePropertyInfo = (~) DataStreamNewlineType
    type AttrBaseTypeConstraint DataInputStreamNewlineTypePropertyInfo = DataInputStreamK
    type AttrGetType DataInputStreamNewlineTypePropertyInfo = DataStreamNewlineType
    type AttrLabel DataInputStreamNewlineTypePropertyInfo = "DataInputStream::newline-type"
    attrGet _ = getDataInputStreamNewlineType
    attrSet _ = setDataInputStreamNewlineType
    attrConstruct _ = constructDataInputStreamNewlineType

type instance AttributeList DataInputStream = DataInputStreamAttributeList
type DataInputStreamAttributeList = ('[ '("base-stream", FilterInputStreamBaseStreamPropertyInfo), '("buffer-size", BufferedInputStreamBufferSizePropertyInfo), '("byte-order", DataInputStreamByteOrderPropertyInfo), '("close-base-stream", FilterInputStreamCloseBaseStreamPropertyInfo), '("newline-type", DataInputStreamNewlineTypePropertyInfo)] :: [(Symbol, *)])

type instance SignalList DataInputStream = DataInputStreamSignalList
type DataInputStreamSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method DataInputStream::new
-- method type : Constructor
-- Args : [Arg {argName = "base_stream", argType = TInterface "Gio" "InputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "base_stream", argType = TInterface "Gio" "InputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "DataInputStream"
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_new" g_data_input_stream_new :: 
    Ptr InputStream ->                      -- base_stream : TInterface "Gio" "InputStream"
    IO (Ptr DataInputStream)


dataInputStreamNew ::
    (MonadIO m, InputStreamK a) =>
    a ->                                    -- base_stream
    m DataInputStream
dataInputStreamNew base_stream = liftIO $ do
    let base_stream' = unsafeManagedPtrCastPtr base_stream
    result <- g_data_input_stream_new base_stream'
    checkUnexpectedReturnNULL "g_data_input_stream_new" result
    result' <- (wrapObject DataInputStream) result
    touchManagedPtr base_stream
    return result'

-- method DataInputStream::get_byte_order
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "DataStreamByteOrder"
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_get_byte_order" g_data_input_stream_get_byte_order :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    IO CUInt


dataInputStreamGetByteOrder ::
    (MonadIO m, DataInputStreamK a) =>
    a ->                                    -- _obj
    m DataStreamByteOrder
dataInputStreamGetByteOrder _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_data_input_stream_get_byte_order _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method DataInputStream::get_newline_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "DataStreamNewlineType"
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_get_newline_type" g_data_input_stream_get_newline_type :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    IO CUInt


dataInputStreamGetNewlineType ::
    (MonadIO m, DataInputStreamK a) =>
    a ->                                    -- _obj
    m DataStreamNewlineType
dataInputStreamGetNewlineType _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- g_data_input_stream_get_newline_type _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method DataInputStream::read_byte
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt8
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_byte" g_data_input_stream_read_byte :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO Word8


dataInputStreamReadByte ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m Word8
dataInputStreamReadByte _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_byte _obj' maybeCancellable
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        return result
     ) (do
        return ()
     )

-- method DataInputStream::read_int16
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt16
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_int16" g_data_input_stream_read_int16 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO Int16


dataInputStreamReadInt16 ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m Int16
dataInputStreamReadInt16 _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_int16 _obj' maybeCancellable
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        return result
     ) (do
        return ()
     )

-- method DataInputStream::read_int32
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_int32" g_data_input_stream_read_int32 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO Int32


dataInputStreamReadInt32 ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m Int32
dataInputStreamReadInt32 _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_int32 _obj' maybeCancellable
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        return result
     ) (do
        return ()
     )

-- method DataInputStream::read_int64
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_int64" g_data_input_stream_read_int64 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO Int64


dataInputStreamReadInt64 ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m Int64
dataInputStreamReadInt64 _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_int64 _obj' maybeCancellable
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        return result
     ) (do
        return ()
     )

-- method DataInputStream::read_line
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUInt8)
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_line" g_data_input_stream_read_line :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Word8)


dataInputStreamReadLine ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m (ByteString,Word64)
dataInputStreamReadLine _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    length_ <- allocMem :: IO (Ptr Word64)
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_line _obj' length_ maybeCancellable
        checkUnexpectedReturnNULL "g_data_input_stream_read_line" result
        result' <- unpackZeroTerminatedByteString result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        freeMem length_
        return (result', length_')
     ) (do
        freeMem length_
     )

-- method DataInputStream::read_line_async
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_read_line_async" g_data_input_stream_read_line_async :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Int32 ->                                -- io_priority : TBasicType TInt32
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    FunPtr AsyncReadyCallbackC ->           -- callback : TInterface "Gio" "AsyncReadyCallback"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


dataInputStreamReadLineAsync ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Int32 ->                                -- io_priority
    Maybe (b) ->                            -- cancellable
    Maybe (AsyncReadyCallback) ->           -- callback
    m ()
dataInputStreamReadLineAsync _obj io_priority cancellable callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    ptrcallback <- callocMem :: IO (Ptr (FunPtr AsyncReadyCallbackC))
    maybeCallback <- case callback of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jCallback -> do
            jCallback' <- mkAsyncReadyCallback (asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
            poke ptrcallback jCallback'
            return jCallback'
    let user_data = nullPtr
    g_data_input_stream_read_line_async _obj' io_priority maybeCancellable maybeCallback user_data
    touchManagedPtr _obj
    whenJust cancellable touchManagedPtr
    return ()

-- method DataInputStream::read_line_finish
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUInt8)
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_line_finish" g_data_input_stream_read_line_finish :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Word8)


dataInputStreamReadLineFinish ::
    (MonadIO m, DataInputStreamK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m (ByteString,Word64)
dataInputStreamReadLineFinish _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    length_ <- allocMem :: IO (Ptr Word64)
    onException (do
        result <- propagateGError $ g_data_input_stream_read_line_finish _obj' result_' length_
        checkUnexpectedReturnNULL "g_data_input_stream_read_line_finish" result
        result' <- unpackZeroTerminatedByteString result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        touchManagedPtr result_
        freeMem length_
        return (result', length_')
     ) (do
        freeMem length_
     )

-- method DataInputStream::read_line_finish_utf8
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_line_finish_utf8" g_data_input_stream_read_line_finish_utf8 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


dataInputStreamReadLineFinishUtf8 ::
    (MonadIO m, DataInputStreamK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m (T.Text,Word64)
dataInputStreamReadLineFinishUtf8 _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    length_ <- allocMem :: IO (Ptr Word64)
    onException (do
        result <- propagateGError $ g_data_input_stream_read_line_finish_utf8 _obj' result_' length_
        checkUnexpectedReturnNULL "g_data_input_stream_read_line_finish_utf8" result
        result' <- cstringToText result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        touchManagedPtr result_
        freeMem length_
        return (result', length_')
     ) (do
        freeMem length_
     )

-- method DataInputStream::read_line_utf8
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_line_utf8" g_data_input_stream_read_line_utf8 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO CString


dataInputStreamReadLineUtf8 ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m (T.Text,Word64)
dataInputStreamReadLineUtf8 _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    length_ <- allocMem :: IO (Ptr Word64)
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_line_utf8 _obj' length_ maybeCancellable
        checkUnexpectedReturnNULL "g_data_input_stream_read_line_utf8" result
        result' <- cstringToText result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        freeMem length_
        return (result', length_')
     ) (do
        freeMem length_
     )

-- method DataInputStream::read_uint16
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt16
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_uint16" g_data_input_stream_read_uint16 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO Word16


dataInputStreamReadUint16 ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m Word16
dataInputStreamReadUint16 _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_uint16 _obj' maybeCancellable
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        return result
     ) (do
        return ()
     )

-- method DataInputStream::read_uint32
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_uint32" g_data_input_stream_read_uint32 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO Word32


dataInputStreamReadUint32 ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m Word32
dataInputStreamReadUint32 _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_uint32 _obj' maybeCancellable
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        return result
     ) (do
        return ()
     )

-- method DataInputStream::read_uint64
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_uint64" g_data_input_stream_read_uint64 :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO Word64


dataInputStreamReadUint64 ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- cancellable
    m Word64
dataInputStreamReadUint64 _obj cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_uint64 _obj' maybeCancellable
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        return result
     ) (do
        return ()
     )

-- method DataInputStream::read_until
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_until" g_data_input_stream_read_until :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    CString ->                              -- stop_chars : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO CString


dataInputStreamReadUntil ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- stop_chars
    Maybe (b) ->                            -- cancellable
    m (T.Text,Word64)
dataInputStreamReadUntil _obj stop_chars cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    stop_chars' <- textToCString stop_chars
    length_ <- allocMem :: IO (Ptr Word64)
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_until _obj' stop_chars' length_ maybeCancellable
        checkUnexpectedReturnNULL "g_data_input_stream_read_until" result
        result' <- cstringToText result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        freeMem stop_chars'
        freeMem length_
        return (result', length_')
     ) (do
        freeMem stop_chars'
        freeMem length_
     )

-- method DataInputStream::read_until_async
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_read_until_async" g_data_input_stream_read_until_async :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    CString ->                              -- stop_chars : TBasicType TUTF8
    Int32 ->                                -- io_priority : TBasicType TInt32
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    FunPtr AsyncReadyCallbackC ->           -- callback : TInterface "Gio" "AsyncReadyCallback"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


dataInputStreamReadUntilAsync ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- stop_chars
    Int32 ->                                -- io_priority
    Maybe (b) ->                            -- cancellable
    Maybe (AsyncReadyCallback) ->           -- callback
    m ()
dataInputStreamReadUntilAsync _obj stop_chars io_priority cancellable callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    stop_chars' <- textToCString stop_chars
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    ptrcallback <- callocMem :: IO (Ptr (FunPtr AsyncReadyCallbackC))
    maybeCallback <- case callback of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jCallback -> do
            jCallback' <- mkAsyncReadyCallback (asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
            poke ptrcallback jCallback'
            return jCallback'
    let user_data = nullPtr
    g_data_input_stream_read_until_async _obj' stop_chars' io_priority maybeCancellable maybeCallback user_data
    touchManagedPtr _obj
    whenJust cancellable touchManagedPtr
    freeMem stop_chars'
    return ()

-- method DataInputStream::read_until_finish
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_until_finish" g_data_input_stream_read_until_finish :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


dataInputStreamReadUntilFinish ::
    (MonadIO m, DataInputStreamK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m (T.Text,Word64)
dataInputStreamReadUntilFinish _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    length_ <- allocMem :: IO (Ptr Word64)
    onException (do
        result <- propagateGError $ g_data_input_stream_read_until_finish _obj' result_' length_
        checkUnexpectedReturnNULL "g_data_input_stream_read_until_finish" result
        result' <- cstringToText result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        touchManagedPtr result_
        freeMem length_
        return (result', length_')
     ) (do
        freeMem length_
     )

-- method DataInputStream::read_upto
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_upto" g_data_input_stream_read_upto :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    CString ->                              -- stop_chars : TBasicType TUTF8
    Int64 ->                                -- stop_chars_len : TBasicType TInt64
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    Ptr (Ptr GError) ->                     -- error
    IO CString


dataInputStreamReadUpto ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- stop_chars
    Int64 ->                                -- stop_chars_len
    Maybe (b) ->                            -- cancellable
    m (T.Text,Word64)
dataInputStreamReadUpto _obj stop_chars stop_chars_len cancellable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    stop_chars' <- textToCString stop_chars
    length_ <- allocMem :: IO (Ptr Word64)
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    onException (do
        result <- propagateGError $ g_data_input_stream_read_upto _obj' stop_chars' stop_chars_len length_ maybeCancellable
        checkUnexpectedReturnNULL "g_data_input_stream_read_upto" result
        result' <- cstringToText result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        whenJust cancellable touchManagedPtr
        freeMem stop_chars'
        freeMem length_
        return (result', length_')
     ) (do
        freeMem stop_chars'
        freeMem length_
     )

-- method DataInputStream::read_upto_async
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 6, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stop_chars_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 6, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_read_upto_async" g_data_input_stream_read_upto_async :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    CString ->                              -- stop_chars : TBasicType TUTF8
    Int64 ->                                -- stop_chars_len : TBasicType TInt64
    Int32 ->                                -- io_priority : TBasicType TInt32
    Ptr Cancellable ->                      -- cancellable : TInterface "Gio" "Cancellable"
    FunPtr AsyncReadyCallbackC ->           -- callback : TInterface "Gio" "AsyncReadyCallback"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


dataInputStreamReadUptoAsync ::
    (MonadIO m, DataInputStreamK a, CancellableK b) =>
    a ->                                    -- _obj
    T.Text ->                               -- stop_chars
    Int64 ->                                -- stop_chars_len
    Int32 ->                                -- io_priority
    Maybe (b) ->                            -- cancellable
    Maybe (AsyncReadyCallback) ->           -- callback
    m ()
dataInputStreamReadUptoAsync _obj stop_chars stop_chars_len io_priority cancellable callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    stop_chars' <- textToCString stop_chars
    maybeCancellable <- case cancellable of
        Nothing -> return nullPtr
        Just jCancellable -> do
            let jCancellable' = unsafeManagedPtrCastPtr jCancellable
            return jCancellable'
    ptrcallback <- callocMem :: IO (Ptr (FunPtr AsyncReadyCallbackC))
    maybeCallback <- case callback of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jCallback -> do
            jCallback' <- mkAsyncReadyCallback (asyncReadyCallbackWrapper (Just ptrcallback) jCallback)
            poke ptrcallback jCallback'
            return jCallback'
    let user_data = nullPtr
    g_data_input_stream_read_upto_async _obj' stop_chars' stop_chars_len io_priority maybeCancellable maybeCallback user_data
    touchManagedPtr _obj
    whenJust cancellable touchManagedPtr
    freeMem stop_chars'
    return ()

-- method DataInputStream::read_upto_finish
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_data_input_stream_read_upto_finish" g_data_input_stream_read_upto_finish :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    Ptr AsyncResult ->                      -- result : TInterface "Gio" "AsyncResult"
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


dataInputStreamReadUptoFinish ::
    (MonadIO m, DataInputStreamK a, AsyncResultK b) =>
    a ->                                    -- _obj
    b ->                                    -- result
    m (T.Text,Word64)
dataInputStreamReadUptoFinish _obj result_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let result_' = unsafeManagedPtrCastPtr result_
    length_ <- allocMem :: IO (Ptr Word64)
    onException (do
        result <- propagateGError $ g_data_input_stream_read_upto_finish _obj' result_' length_
        checkUnexpectedReturnNULL "g_data_input_stream_read_upto_finish" result
        result' <- cstringToText result
        freeMem result
        length_' <- peek length_
        touchManagedPtr _obj
        touchManagedPtr result_
        freeMem length_
        return (result', length_')
     ) (do
        freeMem length_
     )

-- method DataInputStream::set_byte_order
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "order", argType = TInterface "Gio" "DataStreamByteOrder", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "order", argType = TInterface "Gio" "DataStreamByteOrder", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_set_byte_order" g_data_input_stream_set_byte_order :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    CUInt ->                                -- order : TInterface "Gio" "DataStreamByteOrder"
    IO ()


dataInputStreamSetByteOrder ::
    (MonadIO m, DataInputStreamK a) =>
    a ->                                    -- _obj
    DataStreamByteOrder ->                  -- order
    m ()
dataInputStreamSetByteOrder _obj order = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let order' = (fromIntegral . fromEnum) order
    g_data_input_stream_set_byte_order _obj' order'
    touchManagedPtr _obj
    return ()

-- method DataInputStream::set_newline_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gio" "DataStreamNewlineType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DataInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Gio" "DataStreamNewlineType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_data_input_stream_set_newline_type" g_data_input_stream_set_newline_type :: 
    Ptr DataInputStream ->                  -- _obj : TInterface "Gio" "DataInputStream"
    CUInt ->                                -- type : TInterface "Gio" "DataStreamNewlineType"
    IO ()


dataInputStreamSetNewlineType ::
    (MonadIO m, DataInputStreamK a) =>
    a ->                                    -- _obj
    DataStreamNewlineType ->                -- type
    m ()
dataInputStreamSetNewlineType _obj type_ = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let type_' = (fromIntegral . fromEnum) type_
    g_data_input_stream_set_newline_type _obj' type_'
    touchManagedPtr _obj
    return ()