{-# LINE 2 "./System/GIO/Types.chs" #-}
{-# OPTIONS_HADDOCK hide #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
-- -*-haskell-*-
-- -------------------- automatically generated file - do not edit ----------
-- Object hierarchy for the GIMP Toolkit (GTK) Binding for Haskell
--
-- Author : Axel Simon
--
-- Copyright (C) 2001-2005 Axel Simon
--
-- This library is free software; you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public
-- License as published by the Free Software Foundation; either
-- version 2.1 of the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- #hide

-- |
-- Maintainer : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
-- This file reflects the Gtk+ object hierarchy in terms of Haskell classes.
--
-- Note: the mk... functions were originally meant to simply be an alias
-- for the constructor. However, in order to communicate the destructor
-- of an object to objectNew, the mk... functions are now a tuple containing
-- Haskell constructor and the destructor function pointer. This hack avoids
-- changing all modules that simply pass mk... to objectNew.
--
module System.GIO.Types (

  OutputStream(OutputStream), OutputStreamClass,
  toOutputStream,
  mkOutputStream, unOutputStream,
  castToOutputStream, gTypeOutputStream,
  FilterOutputStream(FilterOutputStream), FilterOutputStreamClass,
  toFilterOutputStream,
  mkFilterOutputStream, unFilterOutputStream,
  castToFilterOutputStream, gTypeFilterOutputStream,
  DataOutputStream(DataOutputStream), DataOutputStreamClass,
  toDataOutputStream,
  mkDataOutputStream, unDataOutputStream,
  castToDataOutputStream, gTypeDataOutputStream,
  BufferedOutputStream(BufferedOutputStream), BufferedOutputStreamClass,
  toBufferedOutputStream,
  mkBufferedOutputStream, unBufferedOutputStream,
  castToBufferedOutputStream, gTypeBufferedOutputStream,
  FileOutputStream(FileOutputStream), FileOutputStreamClass,
  toFileOutputStream,
  mkFileOutputStream, unFileOutputStream,
  castToFileOutputStream, gTypeFileOutputStream,
  MemoryOutputStream(MemoryOutputStream), MemoryOutputStreamClass,
  toMemoryOutputStream,
  mkMemoryOutputStream, unMemoryOutputStream,
  castToMemoryOutputStream, gTypeMemoryOutputStream,
  InputStream(InputStream), InputStreamClass,
  toInputStream,
  mkInputStream, unInputStream,
  castToInputStream, gTypeInputStream,
  MemoryInputStream(MemoryInputStream), MemoryInputStreamClass,
  toMemoryInputStream,
  mkMemoryInputStream, unMemoryInputStream,
  castToMemoryInputStream, gTypeMemoryInputStream,
  FilterInputStream(FilterInputStream), FilterInputStreamClass,
  toFilterInputStream,
  mkFilterInputStream, unFilterInputStream,
  castToFilterInputStream, gTypeFilterInputStream,
  BufferedInputStream(BufferedInputStream), BufferedInputStreamClass,
  toBufferedInputStream,
  mkBufferedInputStream, unBufferedInputStream,
  castToBufferedInputStream, gTypeBufferedInputStream,
  DataInputStream(DataInputStream), DataInputStreamClass,
  toDataInputStream,
  mkDataInputStream, unDataInputStream,
  castToDataInputStream, gTypeDataInputStream,
  FileInputStream(FileInputStream), FileInputStreamClass,
  toFileInputStream,
  mkFileInputStream, unFileInputStream,
  castToFileInputStream, gTypeFileInputStream,
  FileMonitor(FileMonitor), FileMonitorClass,
  toFileMonitor,
  mkFileMonitor, unFileMonitor,
  castToFileMonitor, gTypeFileMonitor,
  Vfs(Vfs), VfsClass,
  toVfs,
  mkVfs, unVfs,
  castToVfs, gTypeVfs,
  MountOperation(MountOperation), MountOperationClass,
  toMountOperation,
  mkMountOperation, unMountOperation,
  castToMountOperation, gTypeMountOperation,
  ThemedIcon(ThemedIcon), ThemedIconClass,
  toThemedIcon,
  mkThemedIcon, unThemedIcon,
  castToThemedIcon, gTypeThemedIcon,
  Emblem(Emblem), EmblemClass,
  toEmblem,
  mkEmblem, unEmblem,
  castToEmblem, gTypeEmblem,
  EmblemedIcon(EmblemedIcon), EmblemedIconClass,
  toEmblemedIcon,
  mkEmblemedIcon, unEmblemedIcon,
  castToEmblemedIcon, gTypeEmblemedIcon,
  FileEnumerator(FileEnumerator), FileEnumeratorClass,
  toFileEnumerator,
  mkFileEnumerator, unFileEnumerator,
  castToFileEnumerator, gTypeFileEnumerator,
  FilenameCompleter(FilenameCompleter), FilenameCompleterClass,
  toFilenameCompleter,
  mkFilenameCompleter, unFilenameCompleter,
  castToFilenameCompleter, gTypeFilenameCompleter,
  FileIcon(FileIcon), FileIconClass,
  toFileIcon,
  mkFileIcon, unFileIcon,
  castToFileIcon, gTypeFileIcon,
  VolumeMonitor(VolumeMonitor), VolumeMonitorClass,
  toVolumeMonitor,
  mkVolumeMonitor, unVolumeMonitor,
  castToVolumeMonitor, gTypeVolumeMonitor,
  Cancellable(Cancellable), CancellableClass,
  toCancellable,
  mkCancellable, unCancellable,
  castToCancellable, gTypeCancellable,
  SimpleAsyncResult(SimpleAsyncResult), SimpleAsyncResultClass,
  toSimpleAsyncResult,
  mkSimpleAsyncResult, unSimpleAsyncResult,
  castToSimpleAsyncResult, gTypeSimpleAsyncResult,
  FileInfo(FileInfo), FileInfoClass,
  toFileInfo,
  mkFileInfo, unFileInfo,
  castToFileInfo, gTypeFileInfo,
  AppLaunchContext(AppLaunchContext), AppLaunchContextClass,
  toAppLaunchContext,
  mkAppLaunchContext, unAppLaunchContext,
  castToAppLaunchContext, gTypeAppLaunchContext,
  Icon(Icon), IconClass,
  toIcon,
  mkIcon, unIcon,
  castToIcon, gTypeIcon,
  Seekable(Seekable), SeekableClass,
  toSeekable,
  mkSeekable, unSeekable,
  castToSeekable, gTypeSeekable,
  AppInfo(AppInfo), AppInfoClass,
  toAppInfo,
  mkAppInfo, unAppInfo,
  castToAppInfo, gTypeAppInfo,
  Volume(Volume), VolumeClass,
  toVolume,
  mkVolume, unVolume,
  castToVolume, gTypeVolume,
  AsyncResult(AsyncResult), AsyncResultClass,
  toAsyncResult,
  mkAsyncResult, unAsyncResult,
  castToAsyncResult, gTypeAsyncResult,
  LoadableIcon(LoadableIcon), LoadableIconClass,
  toLoadableIcon,
  mkLoadableIcon, unLoadableIcon,
  castToLoadableIcon, gTypeLoadableIcon,
  Drive(Drive), DriveClass,
  toDrive,
  mkDrive, unDrive,
  castToDrive, gTypeDrive,
  File(File), FileClass,
  toFile,
  mkFile, unFile,
  castToFile, gTypeFile,
  Mount(Mount), MountClass,
  toMount,
  mkMount, unMount,
  castToMount, gTypeMount
  ) where

import Foreign.ForeignPtr (ForeignPtr, castForeignPtr)
-- TODO work around cpphs https:

import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)




import Foreign.C.Types (CULong(..), CUInt(..), CULLong(..))
import System.Glib.GType (GType, typeInstanceIsA)
import System.Glib.GObject


{-# LINE 194 "./System/GIO/Types.chs" #-}

-- The usage of foreignPtrToPtr should be safe as the evaluation will only be
-- forced if the object is used afterwards
--
castTo :: (GObjectClass obj, GObjectClass obj') => GType -> String
                                                -> (obj -> obj')
castTo :: forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gtype String
objTypeName obj
obj =
  case obj -> GObject
forall o. GObjectClass o => o -> GObject
toGObject obj
obj of
    gobj :: GObject
gobj@(GObject ForeignPtr GObject
objFPtr)
      | Ptr () -> GType -> Bool
typeInstanceIsA ((ForeignPtr () -> Ptr ()
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr(ForeignPtr () -> Ptr ())
-> (ForeignPtr GObject -> ForeignPtr ())
-> ForeignPtr GObject
-> Ptr ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.ForeignPtr GObject -> ForeignPtr ()
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr) ForeignPtr GObject
objFPtr) GType
gtype
                  -> GObject -> obj'
forall o. GObjectClass o => GObject -> o
unsafeCastGObject GObject
gobj
      | Bool
otherwise -> String -> obj'
forall a. HasCallStack => String -> a
error (String -> obj') -> String -> obj'
forall a b. (a -> b) -> a -> b
$ String
"Cannot cast object to " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
objTypeName


-- *************************************************************** OutputStream

newtype OutputStream = OutputStream (ForeignPtr (OutputStream)) deriving (OutputStream -> OutputStream -> Bool
(OutputStream -> OutputStream -> Bool)
-> (OutputStream -> OutputStream -> Bool) -> Eq OutputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputStream -> OutputStream -> Bool
== :: OutputStream -> OutputStream -> Bool
$c/= :: OutputStream -> OutputStream -> Bool
/= :: OutputStream -> OutputStream -> Bool
Eq,Eq OutputStream
Eq OutputStream =>
(OutputStream -> OutputStream -> Ordering)
-> (OutputStream -> OutputStream -> Bool)
-> (OutputStream -> OutputStream -> Bool)
-> (OutputStream -> OutputStream -> Bool)
-> (OutputStream -> OutputStream -> Bool)
-> (OutputStream -> OutputStream -> OutputStream)
-> (OutputStream -> OutputStream -> OutputStream)
-> Ord OutputStream
OutputStream -> OutputStream -> Bool
OutputStream -> OutputStream -> Ordering
OutputStream -> OutputStream -> OutputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OutputStream -> OutputStream -> Ordering
compare :: OutputStream -> OutputStream -> Ordering
$c< :: OutputStream -> OutputStream -> Bool
< :: OutputStream -> OutputStream -> Bool
$c<= :: OutputStream -> OutputStream -> Bool
<= :: OutputStream -> OutputStream -> Bool
$c> :: OutputStream -> OutputStream -> Bool
> :: OutputStream -> OutputStream -> Bool
$c>= :: OutputStream -> OutputStream -> Bool
>= :: OutputStream -> OutputStream -> Bool
$cmax :: OutputStream -> OutputStream -> OutputStream
max :: OutputStream -> OutputStream -> OutputStream
$cmin :: OutputStream -> OutputStream -> OutputStream
min :: OutputStream -> OutputStream -> OutputStream
Ord)

mkOutputStream :: (ForeignPtr OutputStream -> OutputStream, FinalizerPtr a)
mkOutputStream = (ForeignPtr OutputStream -> OutputStream
OutputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unOutputStream :: OutputStream -> ForeignPtr OutputStream
unOutputStream (OutputStream ForeignPtr OutputStream
o) = ForeignPtr OutputStream
o

class GObjectClass o => OutputStreamClass o
toOutputStream :: OutputStreamClass o => o -> OutputStream
toOutputStream :: forall o. OutputStreamClass o => o -> OutputStream
toOutputStream = GObject -> OutputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> OutputStream) -> (o -> GObject) -> o -> OutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance OutputStreamClass OutputStream
instance GObjectClass OutputStream where
  toGObject :: OutputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (OutputStream -> ForeignPtr GObject) -> OutputStream -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr OutputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr OutputStream -> ForeignPtr GObject)
-> (OutputStream -> ForeignPtr OutputStream)
-> OutputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OutputStream -> ForeignPtr OutputStream
unOutputStream
  unsafeCastGObject :: GObject -> OutputStream
unsafeCastGObject = ForeignPtr OutputStream -> OutputStream
OutputStream (ForeignPtr OutputStream -> OutputStream)
-> (GObject -> ForeignPtr OutputStream) -> GObject -> OutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr OutputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr OutputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr OutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToOutputStream :: GObjectClass obj => obj -> OutputStream
castToOutputStream :: forall obj. GObjectClass obj => obj -> OutputStream
castToOutputStream = GType -> String -> obj -> OutputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeOutputStream String
"OutputStream"

gTypeOutputStream :: GType
gTypeOutputStream :: GType
gTypeOutputStream =
  GType
g_output_stream_get_type
{-# LINE 230 "./System/GIO/Types.chs" #-}

-- ********************************************************* FilterOutputStream

newtype FilterOutputStream = FilterOutputStream (ForeignPtr (FilterOutputStream)) deriving (FilterOutputStream -> FilterOutputStream -> Bool
(FilterOutputStream -> FilterOutputStream -> Bool)
-> (FilterOutputStream -> FilterOutputStream -> Bool)
-> Eq FilterOutputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FilterOutputStream -> FilterOutputStream -> Bool
== :: FilterOutputStream -> FilterOutputStream -> Bool
$c/= :: FilterOutputStream -> FilterOutputStream -> Bool
/= :: FilterOutputStream -> FilterOutputStream -> Bool
Eq,Eq FilterOutputStream
Eq FilterOutputStream =>
(FilterOutputStream -> FilterOutputStream -> Ordering)
-> (FilterOutputStream -> FilterOutputStream -> Bool)
-> (FilterOutputStream -> FilterOutputStream -> Bool)
-> (FilterOutputStream -> FilterOutputStream -> Bool)
-> (FilterOutputStream -> FilterOutputStream -> Bool)
-> (FilterOutputStream -> FilterOutputStream -> FilterOutputStream)
-> (FilterOutputStream -> FilterOutputStream -> FilterOutputStream)
-> Ord FilterOutputStream
FilterOutputStream -> FilterOutputStream -> Bool
FilterOutputStream -> FilterOutputStream -> Ordering
FilterOutputStream -> FilterOutputStream -> FilterOutputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FilterOutputStream -> FilterOutputStream -> Ordering
compare :: FilterOutputStream -> FilterOutputStream -> Ordering
$c< :: FilterOutputStream -> FilterOutputStream -> Bool
< :: FilterOutputStream -> FilterOutputStream -> Bool
$c<= :: FilterOutputStream -> FilterOutputStream -> Bool
<= :: FilterOutputStream -> FilterOutputStream -> Bool
$c> :: FilterOutputStream -> FilterOutputStream -> Bool
> :: FilterOutputStream -> FilterOutputStream -> Bool
$c>= :: FilterOutputStream -> FilterOutputStream -> Bool
>= :: FilterOutputStream -> FilterOutputStream -> Bool
$cmax :: FilterOutputStream -> FilterOutputStream -> FilterOutputStream
max :: FilterOutputStream -> FilterOutputStream -> FilterOutputStream
$cmin :: FilterOutputStream -> FilterOutputStream -> FilterOutputStream
min :: FilterOutputStream -> FilterOutputStream -> FilterOutputStream
Ord)

mkFilterOutputStream :: (ForeignPtr FilterOutputStream -> FilterOutputStream,
 FinalizerPtr a)
mkFilterOutputStream = (ForeignPtr FilterOutputStream -> FilterOutputStream
FilterOutputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFilterOutputStream :: FilterOutputStream -> ForeignPtr FilterOutputStream
unFilterOutputStream (FilterOutputStream ForeignPtr FilterOutputStream
o) = ForeignPtr FilterOutputStream
o

class OutputStreamClass o => FilterOutputStreamClass o
toFilterOutputStream :: FilterOutputStreamClass o => o -> FilterOutputStream
toFilterOutputStream :: forall o. FilterOutputStreamClass o => o -> FilterOutputStream
toFilterOutputStream = GObject -> FilterOutputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FilterOutputStream)
-> (o -> GObject) -> o -> FilterOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FilterOutputStreamClass FilterOutputStream
instance OutputStreamClass FilterOutputStream
instance GObjectClass FilterOutputStream where
  toGObject :: FilterOutputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FilterOutputStream -> ForeignPtr GObject)
-> FilterOutputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FilterOutputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FilterOutputStream -> ForeignPtr GObject)
-> (FilterOutputStream -> ForeignPtr FilterOutputStream)
-> FilterOutputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilterOutputStream -> ForeignPtr FilterOutputStream
unFilterOutputStream
  unsafeCastGObject :: GObject -> FilterOutputStream
unsafeCastGObject = ForeignPtr FilterOutputStream -> FilterOutputStream
FilterOutputStream (ForeignPtr FilterOutputStream -> FilterOutputStream)
-> (GObject -> ForeignPtr FilterOutputStream)
-> GObject
-> FilterOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FilterOutputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FilterOutputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FilterOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFilterOutputStream :: GObjectClass obj => obj -> FilterOutputStream
castToFilterOutputStream :: forall obj. GObjectClass obj => obj -> FilterOutputStream
castToFilterOutputStream = GType -> String -> obj -> FilterOutputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFilterOutputStream String
"FilterOutputStream"

gTypeFilterOutputStream :: GType
gTypeFilterOutputStream :: GType
gTypeFilterOutputStream =
  GType
g_filter_output_stream_get_type
{-# LINE 254 "./System/GIO/Types.chs" #-}

-- *********************************************************** DataOutputStream

newtype DataOutputStream = DataOutputStream (ForeignPtr (DataOutputStream)) deriving (DataOutputStream -> DataOutputStream -> Bool
(DataOutputStream -> DataOutputStream -> Bool)
-> (DataOutputStream -> DataOutputStream -> Bool)
-> Eq DataOutputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataOutputStream -> DataOutputStream -> Bool
== :: DataOutputStream -> DataOutputStream -> Bool
$c/= :: DataOutputStream -> DataOutputStream -> Bool
/= :: DataOutputStream -> DataOutputStream -> Bool
Eq,Eq DataOutputStream
Eq DataOutputStream =>
(DataOutputStream -> DataOutputStream -> Ordering)
-> (DataOutputStream -> DataOutputStream -> Bool)
-> (DataOutputStream -> DataOutputStream -> Bool)
-> (DataOutputStream -> DataOutputStream -> Bool)
-> (DataOutputStream -> DataOutputStream -> Bool)
-> (DataOutputStream -> DataOutputStream -> DataOutputStream)
-> (DataOutputStream -> DataOutputStream -> DataOutputStream)
-> Ord DataOutputStream
DataOutputStream -> DataOutputStream -> Bool
DataOutputStream -> DataOutputStream -> Ordering
DataOutputStream -> DataOutputStream -> DataOutputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataOutputStream -> DataOutputStream -> Ordering
compare :: DataOutputStream -> DataOutputStream -> Ordering
$c< :: DataOutputStream -> DataOutputStream -> Bool
< :: DataOutputStream -> DataOutputStream -> Bool
$c<= :: DataOutputStream -> DataOutputStream -> Bool
<= :: DataOutputStream -> DataOutputStream -> Bool
$c> :: DataOutputStream -> DataOutputStream -> Bool
> :: DataOutputStream -> DataOutputStream -> Bool
$c>= :: DataOutputStream -> DataOutputStream -> Bool
>= :: DataOutputStream -> DataOutputStream -> Bool
$cmax :: DataOutputStream -> DataOutputStream -> DataOutputStream
max :: DataOutputStream -> DataOutputStream -> DataOutputStream
$cmin :: DataOutputStream -> DataOutputStream -> DataOutputStream
min :: DataOutputStream -> DataOutputStream -> DataOutputStream
Ord)

mkDataOutputStream :: (ForeignPtr DataOutputStream -> DataOutputStream, FinalizerPtr a)
mkDataOutputStream = (ForeignPtr DataOutputStream -> DataOutputStream
DataOutputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unDataOutputStream :: DataOutputStream -> ForeignPtr DataOutputStream
unDataOutputStream (DataOutputStream ForeignPtr DataOutputStream
o) = ForeignPtr DataOutputStream
o

class FilterOutputStreamClass o => DataOutputStreamClass o
toDataOutputStream :: DataOutputStreamClass o => o -> DataOutputStream
toDataOutputStream :: forall o. DataOutputStreamClass o => o -> DataOutputStream
toDataOutputStream = GObject -> DataOutputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> DataOutputStream)
-> (o -> GObject) -> o -> DataOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance DataOutputStreamClass DataOutputStream
instance FilterOutputStreamClass DataOutputStream
instance OutputStreamClass DataOutputStream
instance GObjectClass DataOutputStream where
  toGObject :: DataOutputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (DataOutputStream -> ForeignPtr GObject)
-> DataOutputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr DataOutputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr DataOutputStream -> ForeignPtr GObject)
-> (DataOutputStream -> ForeignPtr DataOutputStream)
-> DataOutputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataOutputStream -> ForeignPtr DataOutputStream
unDataOutputStream
  unsafeCastGObject :: GObject -> DataOutputStream
unsafeCastGObject = ForeignPtr DataOutputStream -> DataOutputStream
DataOutputStream (ForeignPtr DataOutputStream -> DataOutputStream)
-> (GObject -> ForeignPtr DataOutputStream)
-> GObject
-> DataOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr DataOutputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr DataOutputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr DataOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToDataOutputStream :: GObjectClass obj => obj -> DataOutputStream
castToDataOutputStream :: forall obj. GObjectClass obj => obj -> DataOutputStream
castToDataOutputStream = GType -> String -> obj -> DataOutputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeDataOutputStream String
"DataOutputStream"

gTypeDataOutputStream :: GType
gTypeDataOutputStream :: GType
gTypeDataOutputStream =
  GType
g_data_output_stream_get_type
{-# LINE 279 "./System/GIO/Types.chs" #-}

-- ******************************************************* BufferedOutputStream

newtype BufferedOutputStream = BufferedOutputStream (ForeignPtr (BufferedOutputStream)) deriving (BufferedOutputStream -> BufferedOutputStream -> Bool
(BufferedOutputStream -> BufferedOutputStream -> Bool)
-> (BufferedOutputStream -> BufferedOutputStream -> Bool)
-> Eq BufferedOutputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BufferedOutputStream -> BufferedOutputStream -> Bool
== :: BufferedOutputStream -> BufferedOutputStream -> Bool
$c/= :: BufferedOutputStream -> BufferedOutputStream -> Bool
/= :: BufferedOutputStream -> BufferedOutputStream -> Bool
Eq,Eq BufferedOutputStream
Eq BufferedOutputStream =>
(BufferedOutputStream -> BufferedOutputStream -> Ordering)
-> (BufferedOutputStream -> BufferedOutputStream -> Bool)
-> (BufferedOutputStream -> BufferedOutputStream -> Bool)
-> (BufferedOutputStream -> BufferedOutputStream -> Bool)
-> (BufferedOutputStream -> BufferedOutputStream -> Bool)
-> (BufferedOutputStream
    -> BufferedOutputStream -> BufferedOutputStream)
-> (BufferedOutputStream
    -> BufferedOutputStream -> BufferedOutputStream)
-> Ord BufferedOutputStream
BufferedOutputStream -> BufferedOutputStream -> Bool
BufferedOutputStream -> BufferedOutputStream -> Ordering
BufferedOutputStream
-> BufferedOutputStream -> BufferedOutputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BufferedOutputStream -> BufferedOutputStream -> Ordering
compare :: BufferedOutputStream -> BufferedOutputStream -> Ordering
$c< :: BufferedOutputStream -> BufferedOutputStream -> Bool
< :: BufferedOutputStream -> BufferedOutputStream -> Bool
$c<= :: BufferedOutputStream -> BufferedOutputStream -> Bool
<= :: BufferedOutputStream -> BufferedOutputStream -> Bool
$c> :: BufferedOutputStream -> BufferedOutputStream -> Bool
> :: BufferedOutputStream -> BufferedOutputStream -> Bool
$c>= :: BufferedOutputStream -> BufferedOutputStream -> Bool
>= :: BufferedOutputStream -> BufferedOutputStream -> Bool
$cmax :: BufferedOutputStream
-> BufferedOutputStream -> BufferedOutputStream
max :: BufferedOutputStream
-> BufferedOutputStream -> BufferedOutputStream
$cmin :: BufferedOutputStream
-> BufferedOutputStream -> BufferedOutputStream
min :: BufferedOutputStream
-> BufferedOutputStream -> BufferedOutputStream
Ord)

mkBufferedOutputStream :: (ForeignPtr BufferedOutputStream -> BufferedOutputStream,
 FinalizerPtr a)
mkBufferedOutputStream = (ForeignPtr BufferedOutputStream -> BufferedOutputStream
BufferedOutputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unBufferedOutputStream :: BufferedOutputStream -> ForeignPtr BufferedOutputStream
unBufferedOutputStream (BufferedOutputStream ForeignPtr BufferedOutputStream
o) = ForeignPtr BufferedOutputStream
o

class FilterOutputStreamClass o => BufferedOutputStreamClass o
toBufferedOutputStream :: BufferedOutputStreamClass o => o -> BufferedOutputStream
toBufferedOutputStream :: forall o. BufferedOutputStreamClass o => o -> BufferedOutputStream
toBufferedOutputStream = GObject -> BufferedOutputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> BufferedOutputStream)
-> (o -> GObject) -> o -> BufferedOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance BufferedOutputStreamClass BufferedOutputStream
instance FilterOutputStreamClass BufferedOutputStream
instance OutputStreamClass BufferedOutputStream
instance GObjectClass BufferedOutputStream where
  toGObject :: BufferedOutputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (BufferedOutputStream -> ForeignPtr GObject)
-> BufferedOutputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr BufferedOutputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr BufferedOutputStream -> ForeignPtr GObject)
-> (BufferedOutputStream -> ForeignPtr BufferedOutputStream)
-> BufferedOutputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BufferedOutputStream -> ForeignPtr BufferedOutputStream
unBufferedOutputStream
  unsafeCastGObject :: GObject -> BufferedOutputStream
unsafeCastGObject = ForeignPtr BufferedOutputStream -> BufferedOutputStream
BufferedOutputStream (ForeignPtr BufferedOutputStream -> BufferedOutputStream)
-> (GObject -> ForeignPtr BufferedOutputStream)
-> GObject
-> BufferedOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr BufferedOutputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr BufferedOutputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr BufferedOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToBufferedOutputStream :: GObjectClass obj => obj -> BufferedOutputStream
castToBufferedOutputStream :: forall obj. GObjectClass obj => obj -> BufferedOutputStream
castToBufferedOutputStream = GType -> String -> obj -> BufferedOutputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeBufferedOutputStream String
"BufferedOutputStream"

gTypeBufferedOutputStream :: GType
gTypeBufferedOutputStream :: GType
gTypeBufferedOutputStream =
  GType
g_buffered_output_stream_get_type
{-# LINE 304 "./System/GIO/Types.chs" #-}

-- *********************************************************** FileOutputStream

newtype FileOutputStream = FileOutputStream (ForeignPtr (FileOutputStream)) deriving (FileOutputStream -> FileOutputStream -> Bool
(FileOutputStream -> FileOutputStream -> Bool)
-> (FileOutputStream -> FileOutputStream -> Bool)
-> Eq FileOutputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileOutputStream -> FileOutputStream -> Bool
== :: FileOutputStream -> FileOutputStream -> Bool
$c/= :: FileOutputStream -> FileOutputStream -> Bool
/= :: FileOutputStream -> FileOutputStream -> Bool
Eq,Eq FileOutputStream
Eq FileOutputStream =>
(FileOutputStream -> FileOutputStream -> Ordering)
-> (FileOutputStream -> FileOutputStream -> Bool)
-> (FileOutputStream -> FileOutputStream -> Bool)
-> (FileOutputStream -> FileOutputStream -> Bool)
-> (FileOutputStream -> FileOutputStream -> Bool)
-> (FileOutputStream -> FileOutputStream -> FileOutputStream)
-> (FileOutputStream -> FileOutputStream -> FileOutputStream)
-> Ord FileOutputStream
FileOutputStream -> FileOutputStream -> Bool
FileOutputStream -> FileOutputStream -> Ordering
FileOutputStream -> FileOutputStream -> FileOutputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileOutputStream -> FileOutputStream -> Ordering
compare :: FileOutputStream -> FileOutputStream -> Ordering
$c< :: FileOutputStream -> FileOutputStream -> Bool
< :: FileOutputStream -> FileOutputStream -> Bool
$c<= :: FileOutputStream -> FileOutputStream -> Bool
<= :: FileOutputStream -> FileOutputStream -> Bool
$c> :: FileOutputStream -> FileOutputStream -> Bool
> :: FileOutputStream -> FileOutputStream -> Bool
$c>= :: FileOutputStream -> FileOutputStream -> Bool
>= :: FileOutputStream -> FileOutputStream -> Bool
$cmax :: FileOutputStream -> FileOutputStream -> FileOutputStream
max :: FileOutputStream -> FileOutputStream -> FileOutputStream
$cmin :: FileOutputStream -> FileOutputStream -> FileOutputStream
min :: FileOutputStream -> FileOutputStream -> FileOutputStream
Ord)

mkFileOutputStream :: (ForeignPtr FileOutputStream -> FileOutputStream, FinalizerPtr a)
mkFileOutputStream = (ForeignPtr FileOutputStream -> FileOutputStream
FileOutputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFileOutputStream :: FileOutputStream -> ForeignPtr FileOutputStream
unFileOutputStream (FileOutputStream ForeignPtr FileOutputStream
o) = ForeignPtr FileOutputStream
o

class OutputStreamClass o => FileOutputStreamClass o
toFileOutputStream :: FileOutputStreamClass o => o -> FileOutputStream
toFileOutputStream :: forall o. FileOutputStreamClass o => o -> FileOutputStream
toFileOutputStream = GObject -> FileOutputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FileOutputStream)
-> (o -> GObject) -> o -> FileOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FileOutputStreamClass FileOutputStream
instance OutputStreamClass FileOutputStream
instance GObjectClass FileOutputStream where
  toGObject :: FileOutputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FileOutputStream -> ForeignPtr GObject)
-> FileOutputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FileOutputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FileOutputStream -> ForeignPtr GObject)
-> (FileOutputStream -> ForeignPtr FileOutputStream)
-> FileOutputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileOutputStream -> ForeignPtr FileOutputStream
unFileOutputStream
  unsafeCastGObject :: GObject -> FileOutputStream
unsafeCastGObject = ForeignPtr FileOutputStream -> FileOutputStream
FileOutputStream (ForeignPtr FileOutputStream -> FileOutputStream)
-> (GObject -> ForeignPtr FileOutputStream)
-> GObject
-> FileOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FileOutputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FileOutputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FileOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFileOutputStream :: GObjectClass obj => obj -> FileOutputStream
castToFileOutputStream :: forall obj. GObjectClass obj => obj -> FileOutputStream
castToFileOutputStream = GType -> String -> obj -> FileOutputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFileOutputStream String
"FileOutputStream"

gTypeFileOutputStream :: GType
gTypeFileOutputStream :: GType
gTypeFileOutputStream =
  GType
g_file_output_stream_get_type
{-# LINE 328 "./System/GIO/Types.chs" #-}

-- ********************************************************* MemoryOutputStream

newtype MemoryOutputStream = MemoryOutputStream (ForeignPtr (MemoryOutputStream)) deriving (MemoryOutputStream -> MemoryOutputStream -> Bool
(MemoryOutputStream -> MemoryOutputStream -> Bool)
-> (MemoryOutputStream -> MemoryOutputStream -> Bool)
-> Eq MemoryOutputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemoryOutputStream -> MemoryOutputStream -> Bool
== :: MemoryOutputStream -> MemoryOutputStream -> Bool
$c/= :: MemoryOutputStream -> MemoryOutputStream -> Bool
/= :: MemoryOutputStream -> MemoryOutputStream -> Bool
Eq,Eq MemoryOutputStream
Eq MemoryOutputStream =>
(MemoryOutputStream -> MemoryOutputStream -> Ordering)
-> (MemoryOutputStream -> MemoryOutputStream -> Bool)
-> (MemoryOutputStream -> MemoryOutputStream -> Bool)
-> (MemoryOutputStream -> MemoryOutputStream -> Bool)
-> (MemoryOutputStream -> MemoryOutputStream -> Bool)
-> (MemoryOutputStream -> MemoryOutputStream -> MemoryOutputStream)
-> (MemoryOutputStream -> MemoryOutputStream -> MemoryOutputStream)
-> Ord MemoryOutputStream
MemoryOutputStream -> MemoryOutputStream -> Bool
MemoryOutputStream -> MemoryOutputStream -> Ordering
MemoryOutputStream -> MemoryOutputStream -> MemoryOutputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MemoryOutputStream -> MemoryOutputStream -> Ordering
compare :: MemoryOutputStream -> MemoryOutputStream -> Ordering
$c< :: MemoryOutputStream -> MemoryOutputStream -> Bool
< :: MemoryOutputStream -> MemoryOutputStream -> Bool
$c<= :: MemoryOutputStream -> MemoryOutputStream -> Bool
<= :: MemoryOutputStream -> MemoryOutputStream -> Bool
$c> :: MemoryOutputStream -> MemoryOutputStream -> Bool
> :: MemoryOutputStream -> MemoryOutputStream -> Bool
$c>= :: MemoryOutputStream -> MemoryOutputStream -> Bool
>= :: MemoryOutputStream -> MemoryOutputStream -> Bool
$cmax :: MemoryOutputStream -> MemoryOutputStream -> MemoryOutputStream
max :: MemoryOutputStream -> MemoryOutputStream -> MemoryOutputStream
$cmin :: MemoryOutputStream -> MemoryOutputStream -> MemoryOutputStream
min :: MemoryOutputStream -> MemoryOutputStream -> MemoryOutputStream
Ord)

mkMemoryOutputStream :: (ForeignPtr MemoryOutputStream -> MemoryOutputStream,
 FinalizerPtr a)
mkMemoryOutputStream = (ForeignPtr MemoryOutputStream -> MemoryOutputStream
MemoryOutputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unMemoryOutputStream :: MemoryOutputStream -> ForeignPtr MemoryOutputStream
unMemoryOutputStream (MemoryOutputStream ForeignPtr MemoryOutputStream
o) = ForeignPtr MemoryOutputStream
o

class OutputStreamClass o => MemoryOutputStreamClass o
toMemoryOutputStream :: MemoryOutputStreamClass o => o -> MemoryOutputStream
toMemoryOutputStream :: forall o. MemoryOutputStreamClass o => o -> MemoryOutputStream
toMemoryOutputStream = GObject -> MemoryOutputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> MemoryOutputStream)
-> (o -> GObject) -> o -> MemoryOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance MemoryOutputStreamClass MemoryOutputStream
instance OutputStreamClass MemoryOutputStream
instance GObjectClass MemoryOutputStream where
  toGObject :: MemoryOutputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (MemoryOutputStream -> ForeignPtr GObject)
-> MemoryOutputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr MemoryOutputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr MemoryOutputStream -> ForeignPtr GObject)
-> (MemoryOutputStream -> ForeignPtr MemoryOutputStream)
-> MemoryOutputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MemoryOutputStream -> ForeignPtr MemoryOutputStream
unMemoryOutputStream
  unsafeCastGObject :: GObject -> MemoryOutputStream
unsafeCastGObject = ForeignPtr MemoryOutputStream -> MemoryOutputStream
MemoryOutputStream (ForeignPtr MemoryOutputStream -> MemoryOutputStream)
-> (GObject -> ForeignPtr MemoryOutputStream)
-> GObject
-> MemoryOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr MemoryOutputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr MemoryOutputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr MemoryOutputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToMemoryOutputStream :: GObjectClass obj => obj -> MemoryOutputStream
castToMemoryOutputStream :: forall obj. GObjectClass obj => obj -> MemoryOutputStream
castToMemoryOutputStream = GType -> String -> obj -> MemoryOutputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeMemoryOutputStream String
"MemoryOutputStream"

gTypeMemoryOutputStream :: GType
gTypeMemoryOutputStream :: GType
gTypeMemoryOutputStream =
  GType
g_memory_output_stream_get_type
{-# LINE 352 "./System/GIO/Types.chs" #-}

-- **************************************************************** InputStream

newtype InputStream = InputStream (ForeignPtr (InputStream)) deriving (InputStream -> InputStream -> Bool
(InputStream -> InputStream -> Bool)
-> (InputStream -> InputStream -> Bool) -> Eq InputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputStream -> InputStream -> Bool
== :: InputStream -> InputStream -> Bool
$c/= :: InputStream -> InputStream -> Bool
/= :: InputStream -> InputStream -> Bool
Eq,Eq InputStream
Eq InputStream =>
(InputStream -> InputStream -> Ordering)
-> (InputStream -> InputStream -> Bool)
-> (InputStream -> InputStream -> Bool)
-> (InputStream -> InputStream -> Bool)
-> (InputStream -> InputStream -> Bool)
-> (InputStream -> InputStream -> InputStream)
-> (InputStream -> InputStream -> InputStream)
-> Ord InputStream
InputStream -> InputStream -> Bool
InputStream -> InputStream -> Ordering
InputStream -> InputStream -> InputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: InputStream -> InputStream -> Ordering
compare :: InputStream -> InputStream -> Ordering
$c< :: InputStream -> InputStream -> Bool
< :: InputStream -> InputStream -> Bool
$c<= :: InputStream -> InputStream -> Bool
<= :: InputStream -> InputStream -> Bool
$c> :: InputStream -> InputStream -> Bool
> :: InputStream -> InputStream -> Bool
$c>= :: InputStream -> InputStream -> Bool
>= :: InputStream -> InputStream -> Bool
$cmax :: InputStream -> InputStream -> InputStream
max :: InputStream -> InputStream -> InputStream
$cmin :: InputStream -> InputStream -> InputStream
min :: InputStream -> InputStream -> InputStream
Ord)

mkInputStream :: (ForeignPtr InputStream -> InputStream, FinalizerPtr a)
mkInputStream = (ForeignPtr InputStream -> InputStream
InputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unInputStream :: InputStream -> ForeignPtr InputStream
unInputStream (InputStream ForeignPtr InputStream
o) = ForeignPtr InputStream
o

class GObjectClass o => InputStreamClass o
toInputStream :: InputStreamClass o => o -> InputStream
toInputStream :: forall o. InputStreamClass o => o -> InputStream
toInputStream = GObject -> InputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> InputStream) -> (o -> GObject) -> o -> InputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance InputStreamClass InputStream
instance GObjectClass InputStream where
  toGObject :: InputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (InputStream -> ForeignPtr GObject) -> InputStream -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr InputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr InputStream -> ForeignPtr GObject)
-> (InputStream -> ForeignPtr InputStream)
-> InputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputStream -> ForeignPtr InputStream
unInputStream
  unsafeCastGObject :: GObject -> InputStream
unsafeCastGObject = ForeignPtr InputStream -> InputStream
InputStream (ForeignPtr InputStream -> InputStream)
-> (GObject -> ForeignPtr InputStream) -> GObject -> InputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr InputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr InputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr InputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToInputStream :: GObjectClass obj => obj -> InputStream
castToInputStream :: forall obj. GObjectClass obj => obj -> InputStream
castToInputStream = GType -> String -> obj -> InputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeInputStream String
"InputStream"

gTypeInputStream :: GType
gTypeInputStream :: GType
gTypeInputStream =
  GType
g_input_stream_get_type
{-# LINE 375 "./System/GIO/Types.chs" #-}

-- ********************************************************** MemoryInputStream

newtype MemoryInputStream = MemoryInputStream (ForeignPtr (MemoryInputStream)) deriving (MemoryInputStream -> MemoryInputStream -> Bool
(MemoryInputStream -> MemoryInputStream -> Bool)
-> (MemoryInputStream -> MemoryInputStream -> Bool)
-> Eq MemoryInputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemoryInputStream -> MemoryInputStream -> Bool
== :: MemoryInputStream -> MemoryInputStream -> Bool
$c/= :: MemoryInputStream -> MemoryInputStream -> Bool
/= :: MemoryInputStream -> MemoryInputStream -> Bool
Eq,Eq MemoryInputStream
Eq MemoryInputStream =>
(MemoryInputStream -> MemoryInputStream -> Ordering)
-> (MemoryInputStream -> MemoryInputStream -> Bool)
-> (MemoryInputStream -> MemoryInputStream -> Bool)
-> (MemoryInputStream -> MemoryInputStream -> Bool)
-> (MemoryInputStream -> MemoryInputStream -> Bool)
-> (MemoryInputStream -> MemoryInputStream -> MemoryInputStream)
-> (MemoryInputStream -> MemoryInputStream -> MemoryInputStream)
-> Ord MemoryInputStream
MemoryInputStream -> MemoryInputStream -> Bool
MemoryInputStream -> MemoryInputStream -> Ordering
MemoryInputStream -> MemoryInputStream -> MemoryInputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MemoryInputStream -> MemoryInputStream -> Ordering
compare :: MemoryInputStream -> MemoryInputStream -> Ordering
$c< :: MemoryInputStream -> MemoryInputStream -> Bool
< :: MemoryInputStream -> MemoryInputStream -> Bool
$c<= :: MemoryInputStream -> MemoryInputStream -> Bool
<= :: MemoryInputStream -> MemoryInputStream -> Bool
$c> :: MemoryInputStream -> MemoryInputStream -> Bool
> :: MemoryInputStream -> MemoryInputStream -> Bool
$c>= :: MemoryInputStream -> MemoryInputStream -> Bool
>= :: MemoryInputStream -> MemoryInputStream -> Bool
$cmax :: MemoryInputStream -> MemoryInputStream -> MemoryInputStream
max :: MemoryInputStream -> MemoryInputStream -> MemoryInputStream
$cmin :: MemoryInputStream -> MemoryInputStream -> MemoryInputStream
min :: MemoryInputStream -> MemoryInputStream -> MemoryInputStream
Ord)

mkMemoryInputStream :: (ForeignPtr MemoryInputStream -> MemoryInputStream, FinalizerPtr a)
mkMemoryInputStream = (ForeignPtr MemoryInputStream -> MemoryInputStream
MemoryInputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unMemoryInputStream :: MemoryInputStream -> ForeignPtr MemoryInputStream
unMemoryInputStream (MemoryInputStream ForeignPtr MemoryInputStream
o) = ForeignPtr MemoryInputStream
o

class InputStreamClass o => MemoryInputStreamClass o
toMemoryInputStream :: MemoryInputStreamClass o => o -> MemoryInputStream
toMemoryInputStream :: forall o. MemoryInputStreamClass o => o -> MemoryInputStream
toMemoryInputStream = GObject -> MemoryInputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> MemoryInputStream)
-> (o -> GObject) -> o -> MemoryInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance MemoryInputStreamClass MemoryInputStream
instance InputStreamClass MemoryInputStream
instance GObjectClass MemoryInputStream where
  toGObject :: MemoryInputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (MemoryInputStream -> ForeignPtr GObject)
-> MemoryInputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr MemoryInputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr MemoryInputStream -> ForeignPtr GObject)
-> (MemoryInputStream -> ForeignPtr MemoryInputStream)
-> MemoryInputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MemoryInputStream -> ForeignPtr MemoryInputStream
unMemoryInputStream
  unsafeCastGObject :: GObject -> MemoryInputStream
unsafeCastGObject = ForeignPtr MemoryInputStream -> MemoryInputStream
MemoryInputStream (ForeignPtr MemoryInputStream -> MemoryInputStream)
-> (GObject -> ForeignPtr MemoryInputStream)
-> GObject
-> MemoryInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr MemoryInputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr MemoryInputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr MemoryInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToMemoryInputStream :: GObjectClass obj => obj -> MemoryInputStream
castToMemoryInputStream :: forall obj. GObjectClass obj => obj -> MemoryInputStream
castToMemoryInputStream = GType -> String -> obj -> MemoryInputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeMemoryInputStream String
"MemoryInputStream"

gTypeMemoryInputStream :: GType
gTypeMemoryInputStream :: GType
gTypeMemoryInputStream =
  GType
g_memory_input_stream_get_type
{-# LINE 399 "./System/GIO/Types.chs" #-}

-- ********************************************************** FilterInputStream

newtype FilterInputStream = FilterInputStream (ForeignPtr (FilterInputStream)) deriving (FilterInputStream -> FilterInputStream -> Bool
(FilterInputStream -> FilterInputStream -> Bool)
-> (FilterInputStream -> FilterInputStream -> Bool)
-> Eq FilterInputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FilterInputStream -> FilterInputStream -> Bool
== :: FilterInputStream -> FilterInputStream -> Bool
$c/= :: FilterInputStream -> FilterInputStream -> Bool
/= :: FilterInputStream -> FilterInputStream -> Bool
Eq,Eq FilterInputStream
Eq FilterInputStream =>
(FilterInputStream -> FilterInputStream -> Ordering)
-> (FilterInputStream -> FilterInputStream -> Bool)
-> (FilterInputStream -> FilterInputStream -> Bool)
-> (FilterInputStream -> FilterInputStream -> Bool)
-> (FilterInputStream -> FilterInputStream -> Bool)
-> (FilterInputStream -> FilterInputStream -> FilterInputStream)
-> (FilterInputStream -> FilterInputStream -> FilterInputStream)
-> Ord FilterInputStream
FilterInputStream -> FilterInputStream -> Bool
FilterInputStream -> FilterInputStream -> Ordering
FilterInputStream -> FilterInputStream -> FilterInputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FilterInputStream -> FilterInputStream -> Ordering
compare :: FilterInputStream -> FilterInputStream -> Ordering
$c< :: FilterInputStream -> FilterInputStream -> Bool
< :: FilterInputStream -> FilterInputStream -> Bool
$c<= :: FilterInputStream -> FilterInputStream -> Bool
<= :: FilterInputStream -> FilterInputStream -> Bool
$c> :: FilterInputStream -> FilterInputStream -> Bool
> :: FilterInputStream -> FilterInputStream -> Bool
$c>= :: FilterInputStream -> FilterInputStream -> Bool
>= :: FilterInputStream -> FilterInputStream -> Bool
$cmax :: FilterInputStream -> FilterInputStream -> FilterInputStream
max :: FilterInputStream -> FilterInputStream -> FilterInputStream
$cmin :: FilterInputStream -> FilterInputStream -> FilterInputStream
min :: FilterInputStream -> FilterInputStream -> FilterInputStream
Ord)

mkFilterInputStream :: (ForeignPtr FilterInputStream -> FilterInputStream, FinalizerPtr a)
mkFilterInputStream = (ForeignPtr FilterInputStream -> FilterInputStream
FilterInputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFilterInputStream :: FilterInputStream -> ForeignPtr FilterInputStream
unFilterInputStream (FilterInputStream ForeignPtr FilterInputStream
o) = ForeignPtr FilterInputStream
o

class InputStreamClass o => FilterInputStreamClass o
toFilterInputStream :: FilterInputStreamClass o => o -> FilterInputStream
toFilterInputStream :: forall o. FilterInputStreamClass o => o -> FilterInputStream
toFilterInputStream = GObject -> FilterInputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FilterInputStream)
-> (o -> GObject) -> o -> FilterInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FilterInputStreamClass FilterInputStream
instance InputStreamClass FilterInputStream
instance GObjectClass FilterInputStream where
  toGObject :: FilterInputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FilterInputStream -> ForeignPtr GObject)
-> FilterInputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FilterInputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FilterInputStream -> ForeignPtr GObject)
-> (FilterInputStream -> ForeignPtr FilterInputStream)
-> FilterInputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilterInputStream -> ForeignPtr FilterInputStream
unFilterInputStream
  unsafeCastGObject :: GObject -> FilterInputStream
unsafeCastGObject = ForeignPtr FilterInputStream -> FilterInputStream
FilterInputStream (ForeignPtr FilterInputStream -> FilterInputStream)
-> (GObject -> ForeignPtr FilterInputStream)
-> GObject
-> FilterInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FilterInputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FilterInputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FilterInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFilterInputStream :: GObjectClass obj => obj -> FilterInputStream
castToFilterInputStream :: forall obj. GObjectClass obj => obj -> FilterInputStream
castToFilterInputStream = GType -> String -> obj -> FilterInputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFilterInputStream String
"FilterInputStream"

gTypeFilterInputStream :: GType
gTypeFilterInputStream :: GType
gTypeFilterInputStream =
  GType
g_filter_input_stream_get_type
{-# LINE 423 "./System/GIO/Types.chs" #-}

-- ******************************************************** BufferedInputStream

newtype BufferedInputStream = BufferedInputStream (ForeignPtr (BufferedInputStream)) deriving (BufferedInputStream -> BufferedInputStream -> Bool
(BufferedInputStream -> BufferedInputStream -> Bool)
-> (BufferedInputStream -> BufferedInputStream -> Bool)
-> Eq BufferedInputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BufferedInputStream -> BufferedInputStream -> Bool
== :: BufferedInputStream -> BufferedInputStream -> Bool
$c/= :: BufferedInputStream -> BufferedInputStream -> Bool
/= :: BufferedInputStream -> BufferedInputStream -> Bool
Eq,Eq BufferedInputStream
Eq BufferedInputStream =>
(BufferedInputStream -> BufferedInputStream -> Ordering)
-> (BufferedInputStream -> BufferedInputStream -> Bool)
-> (BufferedInputStream -> BufferedInputStream -> Bool)
-> (BufferedInputStream -> BufferedInputStream -> Bool)
-> (BufferedInputStream -> BufferedInputStream -> Bool)
-> (BufferedInputStream
    -> BufferedInputStream -> BufferedInputStream)
-> (BufferedInputStream
    -> BufferedInputStream -> BufferedInputStream)
-> Ord BufferedInputStream
BufferedInputStream -> BufferedInputStream -> Bool
BufferedInputStream -> BufferedInputStream -> Ordering
BufferedInputStream -> BufferedInputStream -> BufferedInputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BufferedInputStream -> BufferedInputStream -> Ordering
compare :: BufferedInputStream -> BufferedInputStream -> Ordering
$c< :: BufferedInputStream -> BufferedInputStream -> Bool
< :: BufferedInputStream -> BufferedInputStream -> Bool
$c<= :: BufferedInputStream -> BufferedInputStream -> Bool
<= :: BufferedInputStream -> BufferedInputStream -> Bool
$c> :: BufferedInputStream -> BufferedInputStream -> Bool
> :: BufferedInputStream -> BufferedInputStream -> Bool
$c>= :: BufferedInputStream -> BufferedInputStream -> Bool
>= :: BufferedInputStream -> BufferedInputStream -> Bool
$cmax :: BufferedInputStream -> BufferedInputStream -> BufferedInputStream
max :: BufferedInputStream -> BufferedInputStream -> BufferedInputStream
$cmin :: BufferedInputStream -> BufferedInputStream -> BufferedInputStream
min :: BufferedInputStream -> BufferedInputStream -> BufferedInputStream
Ord)

mkBufferedInputStream :: (ForeignPtr BufferedInputStream -> BufferedInputStream,
 FinalizerPtr a)
mkBufferedInputStream = (ForeignPtr BufferedInputStream -> BufferedInputStream
BufferedInputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unBufferedInputStream :: BufferedInputStream -> ForeignPtr BufferedInputStream
unBufferedInputStream (BufferedInputStream ForeignPtr BufferedInputStream
o) = ForeignPtr BufferedInputStream
o

class FilterInputStreamClass o => BufferedInputStreamClass o
toBufferedInputStream :: BufferedInputStreamClass o => o -> BufferedInputStream
toBufferedInputStream :: forall o. BufferedInputStreamClass o => o -> BufferedInputStream
toBufferedInputStream = GObject -> BufferedInputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> BufferedInputStream)
-> (o -> GObject) -> o -> BufferedInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance BufferedInputStreamClass BufferedInputStream
instance FilterInputStreamClass BufferedInputStream
instance InputStreamClass BufferedInputStream
instance GObjectClass BufferedInputStream where
  toGObject :: BufferedInputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (BufferedInputStream -> ForeignPtr GObject)
-> BufferedInputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr BufferedInputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr BufferedInputStream -> ForeignPtr GObject)
-> (BufferedInputStream -> ForeignPtr BufferedInputStream)
-> BufferedInputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BufferedInputStream -> ForeignPtr BufferedInputStream
unBufferedInputStream
  unsafeCastGObject :: GObject -> BufferedInputStream
unsafeCastGObject = ForeignPtr BufferedInputStream -> BufferedInputStream
BufferedInputStream (ForeignPtr BufferedInputStream -> BufferedInputStream)
-> (GObject -> ForeignPtr BufferedInputStream)
-> GObject
-> BufferedInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr BufferedInputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr BufferedInputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr BufferedInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToBufferedInputStream :: GObjectClass obj => obj -> BufferedInputStream
castToBufferedInputStream :: forall obj. GObjectClass obj => obj -> BufferedInputStream
castToBufferedInputStream = GType -> String -> obj -> BufferedInputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeBufferedInputStream String
"BufferedInputStream"

gTypeBufferedInputStream :: GType
gTypeBufferedInputStream :: GType
gTypeBufferedInputStream =
  GType
g_buffered_input_stream_get_type
{-# LINE 448 "./System/GIO/Types.chs" #-}

-- ************************************************************ DataInputStream

newtype DataInputStream = DataInputStream (ForeignPtr (DataInputStream)) deriving (DataInputStream -> DataInputStream -> Bool
(DataInputStream -> DataInputStream -> Bool)
-> (DataInputStream -> DataInputStream -> Bool)
-> Eq DataInputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataInputStream -> DataInputStream -> Bool
== :: DataInputStream -> DataInputStream -> Bool
$c/= :: DataInputStream -> DataInputStream -> Bool
/= :: DataInputStream -> DataInputStream -> Bool
Eq,Eq DataInputStream
Eq DataInputStream =>
(DataInputStream -> DataInputStream -> Ordering)
-> (DataInputStream -> DataInputStream -> Bool)
-> (DataInputStream -> DataInputStream -> Bool)
-> (DataInputStream -> DataInputStream -> Bool)
-> (DataInputStream -> DataInputStream -> Bool)
-> (DataInputStream -> DataInputStream -> DataInputStream)
-> (DataInputStream -> DataInputStream -> DataInputStream)
-> Ord DataInputStream
DataInputStream -> DataInputStream -> Bool
DataInputStream -> DataInputStream -> Ordering
DataInputStream -> DataInputStream -> DataInputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataInputStream -> DataInputStream -> Ordering
compare :: DataInputStream -> DataInputStream -> Ordering
$c< :: DataInputStream -> DataInputStream -> Bool
< :: DataInputStream -> DataInputStream -> Bool
$c<= :: DataInputStream -> DataInputStream -> Bool
<= :: DataInputStream -> DataInputStream -> Bool
$c> :: DataInputStream -> DataInputStream -> Bool
> :: DataInputStream -> DataInputStream -> Bool
$c>= :: DataInputStream -> DataInputStream -> Bool
>= :: DataInputStream -> DataInputStream -> Bool
$cmax :: DataInputStream -> DataInputStream -> DataInputStream
max :: DataInputStream -> DataInputStream -> DataInputStream
$cmin :: DataInputStream -> DataInputStream -> DataInputStream
min :: DataInputStream -> DataInputStream -> DataInputStream
Ord)

mkDataInputStream :: (ForeignPtr DataInputStream -> DataInputStream, FinalizerPtr a)
mkDataInputStream = (ForeignPtr DataInputStream -> DataInputStream
DataInputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unDataInputStream :: DataInputStream -> ForeignPtr DataInputStream
unDataInputStream (DataInputStream ForeignPtr DataInputStream
o) = ForeignPtr DataInputStream
o

class BufferedInputStreamClass o => DataInputStreamClass o
toDataInputStream :: DataInputStreamClass o => o -> DataInputStream
toDataInputStream :: forall o. DataInputStreamClass o => o -> DataInputStream
toDataInputStream = GObject -> DataInputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> DataInputStream)
-> (o -> GObject) -> o -> DataInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance DataInputStreamClass DataInputStream
instance BufferedInputStreamClass DataInputStream
instance FilterInputStreamClass DataInputStream
instance InputStreamClass DataInputStream
instance GObjectClass DataInputStream where
  toGObject :: DataInputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (DataInputStream -> ForeignPtr GObject)
-> DataInputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr DataInputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr DataInputStream -> ForeignPtr GObject)
-> (DataInputStream -> ForeignPtr DataInputStream)
-> DataInputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataInputStream -> ForeignPtr DataInputStream
unDataInputStream
  unsafeCastGObject :: GObject -> DataInputStream
unsafeCastGObject = ForeignPtr DataInputStream -> DataInputStream
DataInputStream (ForeignPtr DataInputStream -> DataInputStream)
-> (GObject -> ForeignPtr DataInputStream)
-> GObject
-> DataInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr DataInputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr DataInputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr DataInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToDataInputStream :: GObjectClass obj => obj -> DataInputStream
castToDataInputStream :: forall obj. GObjectClass obj => obj -> DataInputStream
castToDataInputStream = GType -> String -> obj -> DataInputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeDataInputStream String
"DataInputStream"

gTypeDataInputStream :: GType
gTypeDataInputStream :: GType
gTypeDataInputStream =
  GType
g_data_input_stream_get_type
{-# LINE 474 "./System/GIO/Types.chs" #-}

-- ************************************************************ FileInputStream

newtype FileInputStream = FileInputStream (ForeignPtr (FileInputStream)) deriving (FileInputStream -> FileInputStream -> Bool
(FileInputStream -> FileInputStream -> Bool)
-> (FileInputStream -> FileInputStream -> Bool)
-> Eq FileInputStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileInputStream -> FileInputStream -> Bool
== :: FileInputStream -> FileInputStream -> Bool
$c/= :: FileInputStream -> FileInputStream -> Bool
/= :: FileInputStream -> FileInputStream -> Bool
Eq,Eq FileInputStream
Eq FileInputStream =>
(FileInputStream -> FileInputStream -> Ordering)
-> (FileInputStream -> FileInputStream -> Bool)
-> (FileInputStream -> FileInputStream -> Bool)
-> (FileInputStream -> FileInputStream -> Bool)
-> (FileInputStream -> FileInputStream -> Bool)
-> (FileInputStream -> FileInputStream -> FileInputStream)
-> (FileInputStream -> FileInputStream -> FileInputStream)
-> Ord FileInputStream
FileInputStream -> FileInputStream -> Bool
FileInputStream -> FileInputStream -> Ordering
FileInputStream -> FileInputStream -> FileInputStream
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileInputStream -> FileInputStream -> Ordering
compare :: FileInputStream -> FileInputStream -> Ordering
$c< :: FileInputStream -> FileInputStream -> Bool
< :: FileInputStream -> FileInputStream -> Bool
$c<= :: FileInputStream -> FileInputStream -> Bool
<= :: FileInputStream -> FileInputStream -> Bool
$c> :: FileInputStream -> FileInputStream -> Bool
> :: FileInputStream -> FileInputStream -> Bool
$c>= :: FileInputStream -> FileInputStream -> Bool
>= :: FileInputStream -> FileInputStream -> Bool
$cmax :: FileInputStream -> FileInputStream -> FileInputStream
max :: FileInputStream -> FileInputStream -> FileInputStream
$cmin :: FileInputStream -> FileInputStream -> FileInputStream
min :: FileInputStream -> FileInputStream -> FileInputStream
Ord)

mkFileInputStream :: (ForeignPtr FileInputStream -> FileInputStream, FinalizerPtr a)
mkFileInputStream = (ForeignPtr FileInputStream -> FileInputStream
FileInputStream, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFileInputStream :: FileInputStream -> ForeignPtr FileInputStream
unFileInputStream (FileInputStream ForeignPtr FileInputStream
o) = ForeignPtr FileInputStream
o

class InputStreamClass o => FileInputStreamClass o
toFileInputStream :: FileInputStreamClass o => o -> FileInputStream
toFileInputStream :: forall o. FileInputStreamClass o => o -> FileInputStream
toFileInputStream = GObject -> FileInputStream
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FileInputStream)
-> (o -> GObject) -> o -> FileInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FileInputStreamClass FileInputStream
instance InputStreamClass FileInputStream
instance GObjectClass FileInputStream where
  toGObject :: FileInputStream -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FileInputStream -> ForeignPtr GObject)
-> FileInputStream
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FileInputStream -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FileInputStream -> ForeignPtr GObject)
-> (FileInputStream -> ForeignPtr FileInputStream)
-> FileInputStream
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileInputStream -> ForeignPtr FileInputStream
unFileInputStream
  unsafeCastGObject :: GObject -> FileInputStream
unsafeCastGObject = ForeignPtr FileInputStream -> FileInputStream
FileInputStream (ForeignPtr FileInputStream -> FileInputStream)
-> (GObject -> ForeignPtr FileInputStream)
-> GObject
-> FileInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FileInputStream
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FileInputStream)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FileInputStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFileInputStream :: GObjectClass obj => obj -> FileInputStream
castToFileInputStream :: forall obj. GObjectClass obj => obj -> FileInputStream
castToFileInputStream = GType -> String -> obj -> FileInputStream
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFileInputStream String
"FileInputStream"

gTypeFileInputStream :: GType
gTypeFileInputStream :: GType
gTypeFileInputStream =
  GType
g_file_input_stream_get_type
{-# LINE 498 "./System/GIO/Types.chs" #-}

-- **************************************************************** FileMonitor

newtype FileMonitor = FileMonitor (ForeignPtr (FileMonitor)) deriving (FileMonitor -> FileMonitor -> Bool
(FileMonitor -> FileMonitor -> Bool)
-> (FileMonitor -> FileMonitor -> Bool) -> Eq FileMonitor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileMonitor -> FileMonitor -> Bool
== :: FileMonitor -> FileMonitor -> Bool
$c/= :: FileMonitor -> FileMonitor -> Bool
/= :: FileMonitor -> FileMonitor -> Bool
Eq,Eq FileMonitor
Eq FileMonitor =>
(FileMonitor -> FileMonitor -> Ordering)
-> (FileMonitor -> FileMonitor -> Bool)
-> (FileMonitor -> FileMonitor -> Bool)
-> (FileMonitor -> FileMonitor -> Bool)
-> (FileMonitor -> FileMonitor -> Bool)
-> (FileMonitor -> FileMonitor -> FileMonitor)
-> (FileMonitor -> FileMonitor -> FileMonitor)
-> Ord FileMonitor
FileMonitor -> FileMonitor -> Bool
FileMonitor -> FileMonitor -> Ordering
FileMonitor -> FileMonitor -> FileMonitor
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileMonitor -> FileMonitor -> Ordering
compare :: FileMonitor -> FileMonitor -> Ordering
$c< :: FileMonitor -> FileMonitor -> Bool
< :: FileMonitor -> FileMonitor -> Bool
$c<= :: FileMonitor -> FileMonitor -> Bool
<= :: FileMonitor -> FileMonitor -> Bool
$c> :: FileMonitor -> FileMonitor -> Bool
> :: FileMonitor -> FileMonitor -> Bool
$c>= :: FileMonitor -> FileMonitor -> Bool
>= :: FileMonitor -> FileMonitor -> Bool
$cmax :: FileMonitor -> FileMonitor -> FileMonitor
max :: FileMonitor -> FileMonitor -> FileMonitor
$cmin :: FileMonitor -> FileMonitor -> FileMonitor
min :: FileMonitor -> FileMonitor -> FileMonitor
Ord)

mkFileMonitor :: (ForeignPtr FileMonitor -> FileMonitor, FinalizerPtr a)
mkFileMonitor = (ForeignPtr FileMonitor -> FileMonitor
FileMonitor, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFileMonitor :: FileMonitor -> ForeignPtr FileMonitor
unFileMonitor (FileMonitor ForeignPtr FileMonitor
o) = ForeignPtr FileMonitor
o

class GObjectClass o => FileMonitorClass o
toFileMonitor :: FileMonitorClass o => o -> FileMonitor
toFileMonitor :: forall o. FileMonitorClass o => o -> FileMonitor
toFileMonitor = GObject -> FileMonitor
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FileMonitor) -> (o -> GObject) -> o -> FileMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FileMonitorClass FileMonitor
instance GObjectClass FileMonitor where
  toGObject :: FileMonitor -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FileMonitor -> ForeignPtr GObject) -> FileMonitor -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FileMonitor -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FileMonitor -> ForeignPtr GObject)
-> (FileMonitor -> ForeignPtr FileMonitor)
-> FileMonitor
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileMonitor -> ForeignPtr FileMonitor
unFileMonitor
  unsafeCastGObject :: GObject -> FileMonitor
unsafeCastGObject = ForeignPtr FileMonitor -> FileMonitor
FileMonitor (ForeignPtr FileMonitor -> FileMonitor)
-> (GObject -> ForeignPtr FileMonitor) -> GObject -> FileMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FileMonitor
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FileMonitor)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FileMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFileMonitor :: GObjectClass obj => obj -> FileMonitor
castToFileMonitor :: forall obj. GObjectClass obj => obj -> FileMonitor
castToFileMonitor = GType -> String -> obj -> FileMonitor
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFileMonitor String
"FileMonitor"

gTypeFileMonitor :: GType
gTypeFileMonitor :: GType
gTypeFileMonitor =
  GType
g_file_monitor_get_type
{-# LINE 521 "./System/GIO/Types.chs" #-}

-- ************************************************************************ Vfs

newtype Vfs = Vfs (ForeignPtr (Vfs)) deriving (Vfs -> Vfs -> Bool
(Vfs -> Vfs -> Bool) -> (Vfs -> Vfs -> Bool) -> Eq Vfs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Vfs -> Vfs -> Bool
== :: Vfs -> Vfs -> Bool
$c/= :: Vfs -> Vfs -> Bool
/= :: Vfs -> Vfs -> Bool
Eq,Eq Vfs
Eq Vfs =>
(Vfs -> Vfs -> Ordering)
-> (Vfs -> Vfs -> Bool)
-> (Vfs -> Vfs -> Bool)
-> (Vfs -> Vfs -> Bool)
-> (Vfs -> Vfs -> Bool)
-> (Vfs -> Vfs -> Vfs)
-> (Vfs -> Vfs -> Vfs)
-> Ord Vfs
Vfs -> Vfs -> Bool
Vfs -> Vfs -> Ordering
Vfs -> Vfs -> Vfs
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Vfs -> Vfs -> Ordering
compare :: Vfs -> Vfs -> Ordering
$c< :: Vfs -> Vfs -> Bool
< :: Vfs -> Vfs -> Bool
$c<= :: Vfs -> Vfs -> Bool
<= :: Vfs -> Vfs -> Bool
$c> :: Vfs -> Vfs -> Bool
> :: Vfs -> Vfs -> Bool
$c>= :: Vfs -> Vfs -> Bool
>= :: Vfs -> Vfs -> Bool
$cmax :: Vfs -> Vfs -> Vfs
max :: Vfs -> Vfs -> Vfs
$cmin :: Vfs -> Vfs -> Vfs
min :: Vfs -> Vfs -> Vfs
Ord)

mkVfs :: (ForeignPtr Vfs -> Vfs, FinalizerPtr a)
mkVfs = (ForeignPtr Vfs -> Vfs
Vfs, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unVfs :: Vfs -> ForeignPtr Vfs
unVfs (Vfs ForeignPtr Vfs
o) = ForeignPtr Vfs
o

class GObjectClass o => VfsClass o
toVfs :: VfsClass o => o -> Vfs
toVfs :: forall o. VfsClass o => o -> Vfs
toVfs = GObject -> Vfs
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Vfs) -> (o -> GObject) -> o -> Vfs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance VfsClass Vfs
instance GObjectClass Vfs where
  toGObject :: Vfs -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Vfs -> ForeignPtr GObject) -> Vfs -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Vfs -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Vfs -> ForeignPtr GObject)
-> (Vfs -> ForeignPtr Vfs) -> Vfs -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vfs -> ForeignPtr Vfs
unVfs
  unsafeCastGObject :: GObject -> Vfs
unsafeCastGObject = ForeignPtr Vfs -> Vfs
Vfs (ForeignPtr Vfs -> Vfs)
-> (GObject -> ForeignPtr Vfs) -> GObject -> Vfs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Vfs
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Vfs)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr Vfs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToVfs :: GObjectClass obj => obj -> Vfs
castToVfs :: forall obj. GObjectClass obj => obj -> Vfs
castToVfs = GType -> String -> obj -> Vfs
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeVfs String
"Vfs"

gTypeVfs :: GType
gTypeVfs :: GType
gTypeVfs =
  GType
g_vfs_get_type
{-# LINE 544 "./System/GIO/Types.chs" #-}

-- ************************************************************* MountOperation

newtype MountOperation = MountOperation (ForeignPtr (MountOperation)) deriving (MountOperation -> MountOperation -> Bool
(MountOperation -> MountOperation -> Bool)
-> (MountOperation -> MountOperation -> Bool) -> Eq MountOperation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MountOperation -> MountOperation -> Bool
== :: MountOperation -> MountOperation -> Bool
$c/= :: MountOperation -> MountOperation -> Bool
/= :: MountOperation -> MountOperation -> Bool
Eq,Eq MountOperation
Eq MountOperation =>
(MountOperation -> MountOperation -> Ordering)
-> (MountOperation -> MountOperation -> Bool)
-> (MountOperation -> MountOperation -> Bool)
-> (MountOperation -> MountOperation -> Bool)
-> (MountOperation -> MountOperation -> Bool)
-> (MountOperation -> MountOperation -> MountOperation)
-> (MountOperation -> MountOperation -> MountOperation)
-> Ord MountOperation
MountOperation -> MountOperation -> Bool
MountOperation -> MountOperation -> Ordering
MountOperation -> MountOperation -> MountOperation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MountOperation -> MountOperation -> Ordering
compare :: MountOperation -> MountOperation -> Ordering
$c< :: MountOperation -> MountOperation -> Bool
< :: MountOperation -> MountOperation -> Bool
$c<= :: MountOperation -> MountOperation -> Bool
<= :: MountOperation -> MountOperation -> Bool
$c> :: MountOperation -> MountOperation -> Bool
> :: MountOperation -> MountOperation -> Bool
$c>= :: MountOperation -> MountOperation -> Bool
>= :: MountOperation -> MountOperation -> Bool
$cmax :: MountOperation -> MountOperation -> MountOperation
max :: MountOperation -> MountOperation -> MountOperation
$cmin :: MountOperation -> MountOperation -> MountOperation
min :: MountOperation -> MountOperation -> MountOperation
Ord)

mkMountOperation :: (ForeignPtr MountOperation -> MountOperation, FinalizerPtr a)
mkMountOperation = (ForeignPtr MountOperation -> MountOperation
MountOperation, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unMountOperation :: MountOperation -> ForeignPtr MountOperation
unMountOperation (MountOperation ForeignPtr MountOperation
o) = ForeignPtr MountOperation
o

class GObjectClass o => MountOperationClass o
toMountOperation :: MountOperationClass o => o -> MountOperation
toMountOperation :: forall o. MountOperationClass o => o -> MountOperation
toMountOperation = GObject -> MountOperation
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> MountOperation)
-> (o -> GObject) -> o -> MountOperation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance MountOperationClass MountOperation
instance GObjectClass MountOperation where
  toGObject :: MountOperation -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (MountOperation -> ForeignPtr GObject)
-> MountOperation
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr MountOperation -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr MountOperation -> ForeignPtr GObject)
-> (MountOperation -> ForeignPtr MountOperation)
-> MountOperation
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MountOperation -> ForeignPtr MountOperation
unMountOperation
  unsafeCastGObject :: GObject -> MountOperation
unsafeCastGObject = ForeignPtr MountOperation -> MountOperation
MountOperation (ForeignPtr MountOperation -> MountOperation)
-> (GObject -> ForeignPtr MountOperation)
-> GObject
-> MountOperation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr MountOperation
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr MountOperation)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr MountOperation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToMountOperation :: GObjectClass obj => obj -> MountOperation
castToMountOperation :: forall obj. GObjectClass obj => obj -> MountOperation
castToMountOperation = GType -> String -> obj -> MountOperation
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeMountOperation String
"MountOperation"

gTypeMountOperation :: GType
gTypeMountOperation :: GType
gTypeMountOperation =
  GType
g_mount_operation_get_type
{-# LINE 567 "./System/GIO/Types.chs" #-}

-- ***************************************************************** ThemedIcon

newtype ThemedIcon = ThemedIcon (ForeignPtr (ThemedIcon)) deriving (ThemedIcon -> ThemedIcon -> Bool
(ThemedIcon -> ThemedIcon -> Bool)
-> (ThemedIcon -> ThemedIcon -> Bool) -> Eq ThemedIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThemedIcon -> ThemedIcon -> Bool
== :: ThemedIcon -> ThemedIcon -> Bool
$c/= :: ThemedIcon -> ThemedIcon -> Bool
/= :: ThemedIcon -> ThemedIcon -> Bool
Eq,Eq ThemedIcon
Eq ThemedIcon =>
(ThemedIcon -> ThemedIcon -> Ordering)
-> (ThemedIcon -> ThemedIcon -> Bool)
-> (ThemedIcon -> ThemedIcon -> Bool)
-> (ThemedIcon -> ThemedIcon -> Bool)
-> (ThemedIcon -> ThemedIcon -> Bool)
-> (ThemedIcon -> ThemedIcon -> ThemedIcon)
-> (ThemedIcon -> ThemedIcon -> ThemedIcon)
-> Ord ThemedIcon
ThemedIcon -> ThemedIcon -> Bool
ThemedIcon -> ThemedIcon -> Ordering
ThemedIcon -> ThemedIcon -> ThemedIcon
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ThemedIcon -> ThemedIcon -> Ordering
compare :: ThemedIcon -> ThemedIcon -> Ordering
$c< :: ThemedIcon -> ThemedIcon -> Bool
< :: ThemedIcon -> ThemedIcon -> Bool
$c<= :: ThemedIcon -> ThemedIcon -> Bool
<= :: ThemedIcon -> ThemedIcon -> Bool
$c> :: ThemedIcon -> ThemedIcon -> Bool
> :: ThemedIcon -> ThemedIcon -> Bool
$c>= :: ThemedIcon -> ThemedIcon -> Bool
>= :: ThemedIcon -> ThemedIcon -> Bool
$cmax :: ThemedIcon -> ThemedIcon -> ThemedIcon
max :: ThemedIcon -> ThemedIcon -> ThemedIcon
$cmin :: ThemedIcon -> ThemedIcon -> ThemedIcon
min :: ThemedIcon -> ThemedIcon -> ThemedIcon
Ord)

mkThemedIcon :: (ForeignPtr ThemedIcon -> ThemedIcon, FinalizerPtr a)
mkThemedIcon = (ForeignPtr ThemedIcon -> ThemedIcon
ThemedIcon, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unThemedIcon :: ThemedIcon -> ForeignPtr ThemedIcon
unThemedIcon (ThemedIcon ForeignPtr ThemedIcon
o) = ForeignPtr ThemedIcon
o

class GObjectClass o => ThemedIconClass o
toThemedIcon :: ThemedIconClass o => o -> ThemedIcon
toThemedIcon :: forall o. ThemedIconClass o => o -> ThemedIcon
toThemedIcon = GObject -> ThemedIcon
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> ThemedIcon) -> (o -> GObject) -> o -> ThemedIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance ThemedIconClass ThemedIcon
instance GObjectClass ThemedIcon where
  toGObject :: ThemedIcon -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (ThemedIcon -> ForeignPtr GObject) -> ThemedIcon -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr ThemedIcon -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr ThemedIcon -> ForeignPtr GObject)
-> (ThemedIcon -> ForeignPtr ThemedIcon)
-> ThemedIcon
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThemedIcon -> ForeignPtr ThemedIcon
unThemedIcon
  unsafeCastGObject :: GObject -> ThemedIcon
unsafeCastGObject = ForeignPtr ThemedIcon -> ThemedIcon
ThemedIcon (ForeignPtr ThemedIcon -> ThemedIcon)
-> (GObject -> ForeignPtr ThemedIcon) -> GObject -> ThemedIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr ThemedIcon
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr ThemedIcon)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr ThemedIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToThemedIcon :: GObjectClass obj => obj -> ThemedIcon
castToThemedIcon :: forall obj. GObjectClass obj => obj -> ThemedIcon
castToThemedIcon = GType -> String -> obj -> ThemedIcon
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeThemedIcon String
"ThemedIcon"

gTypeThemedIcon :: GType
gTypeThemedIcon :: GType
gTypeThemedIcon =
  GType
g_themed_icon_get_type
{-# LINE 590 "./System/GIO/Types.chs" #-}

-- ********************************************************************* Emblem

newtype Emblem = Emblem (ForeignPtr (Emblem)) deriving (Emblem -> Emblem -> Bool
(Emblem -> Emblem -> Bool)
-> (Emblem -> Emblem -> Bool) -> Eq Emblem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Emblem -> Emblem -> Bool
== :: Emblem -> Emblem -> Bool
$c/= :: Emblem -> Emblem -> Bool
/= :: Emblem -> Emblem -> Bool
Eq,Eq Emblem
Eq Emblem =>
(Emblem -> Emblem -> Ordering)
-> (Emblem -> Emblem -> Bool)
-> (Emblem -> Emblem -> Bool)
-> (Emblem -> Emblem -> Bool)
-> (Emblem -> Emblem -> Bool)
-> (Emblem -> Emblem -> Emblem)
-> (Emblem -> Emblem -> Emblem)
-> Ord Emblem
Emblem -> Emblem -> Bool
Emblem -> Emblem -> Ordering
Emblem -> Emblem -> Emblem
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Emblem -> Emblem -> Ordering
compare :: Emblem -> Emblem -> Ordering
$c< :: Emblem -> Emblem -> Bool
< :: Emblem -> Emblem -> Bool
$c<= :: Emblem -> Emblem -> Bool
<= :: Emblem -> Emblem -> Bool
$c> :: Emblem -> Emblem -> Bool
> :: Emblem -> Emblem -> Bool
$c>= :: Emblem -> Emblem -> Bool
>= :: Emblem -> Emblem -> Bool
$cmax :: Emblem -> Emblem -> Emblem
max :: Emblem -> Emblem -> Emblem
$cmin :: Emblem -> Emblem -> Emblem
min :: Emblem -> Emblem -> Emblem
Ord)

mkEmblem :: (ForeignPtr Emblem -> Emblem, FinalizerPtr a)
mkEmblem = (ForeignPtr Emblem -> Emblem
Emblem, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unEmblem :: Emblem -> ForeignPtr Emblem
unEmblem (Emblem ForeignPtr Emblem
o) = ForeignPtr Emblem
o

class GObjectClass o => EmblemClass o
toEmblem :: EmblemClass o => o -> Emblem
toEmblem :: forall o. EmblemClass o => o -> Emblem
toEmblem = GObject -> Emblem
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Emblem) -> (o -> GObject) -> o -> Emblem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance EmblemClass Emblem
instance GObjectClass Emblem where
  toGObject :: Emblem -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Emblem -> ForeignPtr GObject) -> Emblem -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Emblem -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Emblem -> ForeignPtr GObject)
-> (Emblem -> ForeignPtr Emblem) -> Emblem -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Emblem -> ForeignPtr Emblem
unEmblem
  unsafeCastGObject :: GObject -> Emblem
unsafeCastGObject = ForeignPtr Emblem -> Emblem
Emblem (ForeignPtr Emblem -> Emblem)
-> (GObject -> ForeignPtr Emblem) -> GObject -> Emblem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Emblem
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Emblem)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr Emblem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToEmblem :: GObjectClass obj => obj -> Emblem
castToEmblem :: forall obj. GObjectClass obj => obj -> Emblem
castToEmblem = GType -> String -> obj -> Emblem
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeEmblem String
"Emblem"

gTypeEmblem :: GType
gTypeEmblem :: GType
gTypeEmblem =
  GType
g_emblem_get_type
{-# LINE 613 "./System/GIO/Types.chs" #-}

-- *************************************************************** EmblemedIcon

newtype EmblemedIcon = EmblemedIcon (ForeignPtr (EmblemedIcon)) deriving (EmblemedIcon -> EmblemedIcon -> Bool
(EmblemedIcon -> EmblemedIcon -> Bool)
-> (EmblemedIcon -> EmblemedIcon -> Bool) -> Eq EmblemedIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EmblemedIcon -> EmblemedIcon -> Bool
== :: EmblemedIcon -> EmblemedIcon -> Bool
$c/= :: EmblemedIcon -> EmblemedIcon -> Bool
/= :: EmblemedIcon -> EmblemedIcon -> Bool
Eq,Eq EmblemedIcon
Eq EmblemedIcon =>
(EmblemedIcon -> EmblemedIcon -> Ordering)
-> (EmblemedIcon -> EmblemedIcon -> Bool)
-> (EmblemedIcon -> EmblemedIcon -> Bool)
-> (EmblemedIcon -> EmblemedIcon -> Bool)
-> (EmblemedIcon -> EmblemedIcon -> Bool)
-> (EmblemedIcon -> EmblemedIcon -> EmblemedIcon)
-> (EmblemedIcon -> EmblemedIcon -> EmblemedIcon)
-> Ord EmblemedIcon
EmblemedIcon -> EmblemedIcon -> Bool
EmblemedIcon -> EmblemedIcon -> Ordering
EmblemedIcon -> EmblemedIcon -> EmblemedIcon
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EmblemedIcon -> EmblemedIcon -> Ordering
compare :: EmblemedIcon -> EmblemedIcon -> Ordering
$c< :: EmblemedIcon -> EmblemedIcon -> Bool
< :: EmblemedIcon -> EmblemedIcon -> Bool
$c<= :: EmblemedIcon -> EmblemedIcon -> Bool
<= :: EmblemedIcon -> EmblemedIcon -> Bool
$c> :: EmblemedIcon -> EmblemedIcon -> Bool
> :: EmblemedIcon -> EmblemedIcon -> Bool
$c>= :: EmblemedIcon -> EmblemedIcon -> Bool
>= :: EmblemedIcon -> EmblemedIcon -> Bool
$cmax :: EmblemedIcon -> EmblemedIcon -> EmblemedIcon
max :: EmblemedIcon -> EmblemedIcon -> EmblemedIcon
$cmin :: EmblemedIcon -> EmblemedIcon -> EmblemedIcon
min :: EmblemedIcon -> EmblemedIcon -> EmblemedIcon
Ord)

mkEmblemedIcon :: (ForeignPtr EmblemedIcon -> EmblemedIcon, FinalizerPtr a)
mkEmblemedIcon = (ForeignPtr EmblemedIcon -> EmblemedIcon
EmblemedIcon, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unEmblemedIcon :: EmblemedIcon -> ForeignPtr EmblemedIcon
unEmblemedIcon (EmblemedIcon ForeignPtr EmblemedIcon
o) = ForeignPtr EmblemedIcon
o

class GObjectClass o => EmblemedIconClass o
toEmblemedIcon :: EmblemedIconClass o => o -> EmblemedIcon
toEmblemedIcon :: forall o. EmblemedIconClass o => o -> EmblemedIcon
toEmblemedIcon = GObject -> EmblemedIcon
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> EmblemedIcon) -> (o -> GObject) -> o -> EmblemedIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance EmblemedIconClass EmblemedIcon
instance GObjectClass EmblemedIcon where
  toGObject :: EmblemedIcon -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (EmblemedIcon -> ForeignPtr GObject) -> EmblemedIcon -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr EmblemedIcon -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr EmblemedIcon -> ForeignPtr GObject)
-> (EmblemedIcon -> ForeignPtr EmblemedIcon)
-> EmblemedIcon
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EmblemedIcon -> ForeignPtr EmblemedIcon
unEmblemedIcon
  unsafeCastGObject :: GObject -> EmblemedIcon
unsafeCastGObject = ForeignPtr EmblemedIcon -> EmblemedIcon
EmblemedIcon (ForeignPtr EmblemedIcon -> EmblemedIcon)
-> (GObject -> ForeignPtr EmblemedIcon) -> GObject -> EmblemedIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr EmblemedIcon
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr EmblemedIcon)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr EmblemedIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToEmblemedIcon :: GObjectClass obj => obj -> EmblemedIcon
castToEmblemedIcon :: forall obj. GObjectClass obj => obj -> EmblemedIcon
castToEmblemedIcon = GType -> String -> obj -> EmblemedIcon
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeEmblemedIcon String
"EmblemedIcon"

gTypeEmblemedIcon :: GType
gTypeEmblemedIcon :: GType
gTypeEmblemedIcon =
  GType
g_emblemed_icon_get_type
{-# LINE 636 "./System/GIO/Types.chs" #-}

-- ************************************************************* FileEnumerator

newtype FileEnumerator = FileEnumerator (ForeignPtr (FileEnumerator)) deriving (FileEnumerator -> FileEnumerator -> Bool
(FileEnumerator -> FileEnumerator -> Bool)
-> (FileEnumerator -> FileEnumerator -> Bool) -> Eq FileEnumerator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileEnumerator -> FileEnumerator -> Bool
== :: FileEnumerator -> FileEnumerator -> Bool
$c/= :: FileEnumerator -> FileEnumerator -> Bool
/= :: FileEnumerator -> FileEnumerator -> Bool
Eq,Eq FileEnumerator
Eq FileEnumerator =>
(FileEnumerator -> FileEnumerator -> Ordering)
-> (FileEnumerator -> FileEnumerator -> Bool)
-> (FileEnumerator -> FileEnumerator -> Bool)
-> (FileEnumerator -> FileEnumerator -> Bool)
-> (FileEnumerator -> FileEnumerator -> Bool)
-> (FileEnumerator -> FileEnumerator -> FileEnumerator)
-> (FileEnumerator -> FileEnumerator -> FileEnumerator)
-> Ord FileEnumerator
FileEnumerator -> FileEnumerator -> Bool
FileEnumerator -> FileEnumerator -> Ordering
FileEnumerator -> FileEnumerator -> FileEnumerator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileEnumerator -> FileEnumerator -> Ordering
compare :: FileEnumerator -> FileEnumerator -> Ordering
$c< :: FileEnumerator -> FileEnumerator -> Bool
< :: FileEnumerator -> FileEnumerator -> Bool
$c<= :: FileEnumerator -> FileEnumerator -> Bool
<= :: FileEnumerator -> FileEnumerator -> Bool
$c> :: FileEnumerator -> FileEnumerator -> Bool
> :: FileEnumerator -> FileEnumerator -> Bool
$c>= :: FileEnumerator -> FileEnumerator -> Bool
>= :: FileEnumerator -> FileEnumerator -> Bool
$cmax :: FileEnumerator -> FileEnumerator -> FileEnumerator
max :: FileEnumerator -> FileEnumerator -> FileEnumerator
$cmin :: FileEnumerator -> FileEnumerator -> FileEnumerator
min :: FileEnumerator -> FileEnumerator -> FileEnumerator
Ord)

mkFileEnumerator :: (ForeignPtr FileEnumerator -> FileEnumerator, FinalizerPtr a)
mkFileEnumerator = (ForeignPtr FileEnumerator -> FileEnumerator
FileEnumerator, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFileEnumerator :: FileEnumerator -> ForeignPtr FileEnumerator
unFileEnumerator (FileEnumerator ForeignPtr FileEnumerator
o) = ForeignPtr FileEnumerator
o

class GObjectClass o => FileEnumeratorClass o
toFileEnumerator :: FileEnumeratorClass o => o -> FileEnumerator
toFileEnumerator :: forall o. FileEnumeratorClass o => o -> FileEnumerator
toFileEnumerator = GObject -> FileEnumerator
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FileEnumerator)
-> (o -> GObject) -> o -> FileEnumerator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FileEnumeratorClass FileEnumerator
instance GObjectClass FileEnumerator where
  toGObject :: FileEnumerator -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FileEnumerator -> ForeignPtr GObject)
-> FileEnumerator
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FileEnumerator -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FileEnumerator -> ForeignPtr GObject)
-> (FileEnumerator -> ForeignPtr FileEnumerator)
-> FileEnumerator
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileEnumerator -> ForeignPtr FileEnumerator
unFileEnumerator
  unsafeCastGObject :: GObject -> FileEnumerator
unsafeCastGObject = ForeignPtr FileEnumerator -> FileEnumerator
FileEnumerator (ForeignPtr FileEnumerator -> FileEnumerator)
-> (GObject -> ForeignPtr FileEnumerator)
-> GObject
-> FileEnumerator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FileEnumerator
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FileEnumerator)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FileEnumerator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFileEnumerator :: GObjectClass obj => obj -> FileEnumerator
castToFileEnumerator :: forall obj. GObjectClass obj => obj -> FileEnumerator
castToFileEnumerator = GType -> String -> obj -> FileEnumerator
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFileEnumerator String
"FileEnumerator"

gTypeFileEnumerator :: GType
gTypeFileEnumerator :: GType
gTypeFileEnumerator =
  GType
g_file_enumerator_get_type
{-# LINE 659 "./System/GIO/Types.chs" #-}

-- ********************************************************** FilenameCompleter

newtype FilenameCompleter = FilenameCompleter (ForeignPtr (FilenameCompleter)) deriving (FilenameCompleter -> FilenameCompleter -> Bool
(FilenameCompleter -> FilenameCompleter -> Bool)
-> (FilenameCompleter -> FilenameCompleter -> Bool)
-> Eq FilenameCompleter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FilenameCompleter -> FilenameCompleter -> Bool
== :: FilenameCompleter -> FilenameCompleter -> Bool
$c/= :: FilenameCompleter -> FilenameCompleter -> Bool
/= :: FilenameCompleter -> FilenameCompleter -> Bool
Eq,Eq FilenameCompleter
Eq FilenameCompleter =>
(FilenameCompleter -> FilenameCompleter -> Ordering)
-> (FilenameCompleter -> FilenameCompleter -> Bool)
-> (FilenameCompleter -> FilenameCompleter -> Bool)
-> (FilenameCompleter -> FilenameCompleter -> Bool)
-> (FilenameCompleter -> FilenameCompleter -> Bool)
-> (FilenameCompleter -> FilenameCompleter -> FilenameCompleter)
-> (FilenameCompleter -> FilenameCompleter -> FilenameCompleter)
-> Ord FilenameCompleter
FilenameCompleter -> FilenameCompleter -> Bool
FilenameCompleter -> FilenameCompleter -> Ordering
FilenameCompleter -> FilenameCompleter -> FilenameCompleter
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FilenameCompleter -> FilenameCompleter -> Ordering
compare :: FilenameCompleter -> FilenameCompleter -> Ordering
$c< :: FilenameCompleter -> FilenameCompleter -> Bool
< :: FilenameCompleter -> FilenameCompleter -> Bool
$c<= :: FilenameCompleter -> FilenameCompleter -> Bool
<= :: FilenameCompleter -> FilenameCompleter -> Bool
$c> :: FilenameCompleter -> FilenameCompleter -> Bool
> :: FilenameCompleter -> FilenameCompleter -> Bool
$c>= :: FilenameCompleter -> FilenameCompleter -> Bool
>= :: FilenameCompleter -> FilenameCompleter -> Bool
$cmax :: FilenameCompleter -> FilenameCompleter -> FilenameCompleter
max :: FilenameCompleter -> FilenameCompleter -> FilenameCompleter
$cmin :: FilenameCompleter -> FilenameCompleter -> FilenameCompleter
min :: FilenameCompleter -> FilenameCompleter -> FilenameCompleter
Ord)

mkFilenameCompleter :: (ForeignPtr FilenameCompleter -> FilenameCompleter, FinalizerPtr a)
mkFilenameCompleter = (ForeignPtr FilenameCompleter -> FilenameCompleter
FilenameCompleter, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFilenameCompleter :: FilenameCompleter -> ForeignPtr FilenameCompleter
unFilenameCompleter (FilenameCompleter ForeignPtr FilenameCompleter
o) = ForeignPtr FilenameCompleter
o

class GObjectClass o => FilenameCompleterClass o
toFilenameCompleter :: FilenameCompleterClass o => o -> FilenameCompleter
toFilenameCompleter :: forall o. FilenameCompleterClass o => o -> FilenameCompleter
toFilenameCompleter = GObject -> FilenameCompleter
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FilenameCompleter)
-> (o -> GObject) -> o -> FilenameCompleter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FilenameCompleterClass FilenameCompleter
instance GObjectClass FilenameCompleter where
  toGObject :: FilenameCompleter -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FilenameCompleter -> ForeignPtr GObject)
-> FilenameCompleter
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FilenameCompleter -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FilenameCompleter -> ForeignPtr GObject)
-> (FilenameCompleter -> ForeignPtr FilenameCompleter)
-> FilenameCompleter
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilenameCompleter -> ForeignPtr FilenameCompleter
unFilenameCompleter
  unsafeCastGObject :: GObject -> FilenameCompleter
unsafeCastGObject = ForeignPtr FilenameCompleter -> FilenameCompleter
FilenameCompleter (ForeignPtr FilenameCompleter -> FilenameCompleter)
-> (GObject -> ForeignPtr FilenameCompleter)
-> GObject
-> FilenameCompleter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FilenameCompleter
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FilenameCompleter)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FilenameCompleter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFilenameCompleter :: GObjectClass obj => obj -> FilenameCompleter
castToFilenameCompleter :: forall obj. GObjectClass obj => obj -> FilenameCompleter
castToFilenameCompleter = GType -> String -> obj -> FilenameCompleter
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFilenameCompleter String
"FilenameCompleter"

gTypeFilenameCompleter :: GType
gTypeFilenameCompleter :: GType
gTypeFilenameCompleter =
  GType
g_filename_completer_get_type
{-# LINE 682 "./System/GIO/Types.chs" #-}

-- ******************************************************************* FileIcon

newtype FileIcon = FileIcon (ForeignPtr (FileIcon)) deriving (FileIcon -> FileIcon -> Bool
(FileIcon -> FileIcon -> Bool)
-> (FileIcon -> FileIcon -> Bool) -> Eq FileIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileIcon -> FileIcon -> Bool
== :: FileIcon -> FileIcon -> Bool
$c/= :: FileIcon -> FileIcon -> Bool
/= :: FileIcon -> FileIcon -> Bool
Eq,Eq FileIcon
Eq FileIcon =>
(FileIcon -> FileIcon -> Ordering)
-> (FileIcon -> FileIcon -> Bool)
-> (FileIcon -> FileIcon -> Bool)
-> (FileIcon -> FileIcon -> Bool)
-> (FileIcon -> FileIcon -> Bool)
-> (FileIcon -> FileIcon -> FileIcon)
-> (FileIcon -> FileIcon -> FileIcon)
-> Ord FileIcon
FileIcon -> FileIcon -> Bool
FileIcon -> FileIcon -> Ordering
FileIcon -> FileIcon -> FileIcon
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileIcon -> FileIcon -> Ordering
compare :: FileIcon -> FileIcon -> Ordering
$c< :: FileIcon -> FileIcon -> Bool
< :: FileIcon -> FileIcon -> Bool
$c<= :: FileIcon -> FileIcon -> Bool
<= :: FileIcon -> FileIcon -> Bool
$c> :: FileIcon -> FileIcon -> Bool
> :: FileIcon -> FileIcon -> Bool
$c>= :: FileIcon -> FileIcon -> Bool
>= :: FileIcon -> FileIcon -> Bool
$cmax :: FileIcon -> FileIcon -> FileIcon
max :: FileIcon -> FileIcon -> FileIcon
$cmin :: FileIcon -> FileIcon -> FileIcon
min :: FileIcon -> FileIcon -> FileIcon
Ord)

mkFileIcon :: (ForeignPtr FileIcon -> FileIcon, FinalizerPtr a)
mkFileIcon = (ForeignPtr FileIcon -> FileIcon
FileIcon, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFileIcon :: FileIcon -> ForeignPtr FileIcon
unFileIcon (FileIcon ForeignPtr FileIcon
o) = ForeignPtr FileIcon
o

class GObjectClass o => FileIconClass o
toFileIcon :: FileIconClass o => o -> FileIcon
toFileIcon :: forall o. FileIconClass o => o -> FileIcon
toFileIcon = GObject -> FileIcon
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FileIcon) -> (o -> GObject) -> o -> FileIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FileIconClass FileIcon
instance GObjectClass FileIcon where
  toGObject :: FileIcon -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FileIcon -> ForeignPtr GObject) -> FileIcon -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FileIcon -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FileIcon -> ForeignPtr GObject)
-> (FileIcon -> ForeignPtr FileIcon)
-> FileIcon
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileIcon -> ForeignPtr FileIcon
unFileIcon
  unsafeCastGObject :: GObject -> FileIcon
unsafeCastGObject = ForeignPtr FileIcon -> FileIcon
FileIcon (ForeignPtr FileIcon -> FileIcon)
-> (GObject -> ForeignPtr FileIcon) -> GObject -> FileIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FileIcon
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FileIcon)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FileIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFileIcon :: GObjectClass obj => obj -> FileIcon
castToFileIcon :: forall obj. GObjectClass obj => obj -> FileIcon
castToFileIcon = GType -> String -> obj -> FileIcon
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFileIcon String
"FileIcon"

gTypeFileIcon :: GType
gTypeFileIcon :: GType
gTypeFileIcon =
  GType
g_file_icon_get_type
{-# LINE 705 "./System/GIO/Types.chs" #-}

-- ************************************************************** VolumeMonitor

newtype VolumeMonitor = VolumeMonitor (ForeignPtr (VolumeMonitor)) deriving (VolumeMonitor -> VolumeMonitor -> Bool
(VolumeMonitor -> VolumeMonitor -> Bool)
-> (VolumeMonitor -> VolumeMonitor -> Bool) -> Eq VolumeMonitor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VolumeMonitor -> VolumeMonitor -> Bool
== :: VolumeMonitor -> VolumeMonitor -> Bool
$c/= :: VolumeMonitor -> VolumeMonitor -> Bool
/= :: VolumeMonitor -> VolumeMonitor -> Bool
Eq,Eq VolumeMonitor
Eq VolumeMonitor =>
(VolumeMonitor -> VolumeMonitor -> Ordering)
-> (VolumeMonitor -> VolumeMonitor -> Bool)
-> (VolumeMonitor -> VolumeMonitor -> Bool)
-> (VolumeMonitor -> VolumeMonitor -> Bool)
-> (VolumeMonitor -> VolumeMonitor -> Bool)
-> (VolumeMonitor -> VolumeMonitor -> VolumeMonitor)
-> (VolumeMonitor -> VolumeMonitor -> VolumeMonitor)
-> Ord VolumeMonitor
VolumeMonitor -> VolumeMonitor -> Bool
VolumeMonitor -> VolumeMonitor -> Ordering
VolumeMonitor -> VolumeMonitor -> VolumeMonitor
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: VolumeMonitor -> VolumeMonitor -> Ordering
compare :: VolumeMonitor -> VolumeMonitor -> Ordering
$c< :: VolumeMonitor -> VolumeMonitor -> Bool
< :: VolumeMonitor -> VolumeMonitor -> Bool
$c<= :: VolumeMonitor -> VolumeMonitor -> Bool
<= :: VolumeMonitor -> VolumeMonitor -> Bool
$c> :: VolumeMonitor -> VolumeMonitor -> Bool
> :: VolumeMonitor -> VolumeMonitor -> Bool
$c>= :: VolumeMonitor -> VolumeMonitor -> Bool
>= :: VolumeMonitor -> VolumeMonitor -> Bool
$cmax :: VolumeMonitor -> VolumeMonitor -> VolumeMonitor
max :: VolumeMonitor -> VolumeMonitor -> VolumeMonitor
$cmin :: VolumeMonitor -> VolumeMonitor -> VolumeMonitor
min :: VolumeMonitor -> VolumeMonitor -> VolumeMonitor
Ord)

mkVolumeMonitor :: (ForeignPtr VolumeMonitor -> VolumeMonitor, FinalizerPtr a)
mkVolumeMonitor = (ForeignPtr VolumeMonitor -> VolumeMonitor
VolumeMonitor, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unVolumeMonitor :: VolumeMonitor -> ForeignPtr VolumeMonitor
unVolumeMonitor (VolumeMonitor ForeignPtr VolumeMonitor
o) = ForeignPtr VolumeMonitor
o

class GObjectClass o => VolumeMonitorClass o
toVolumeMonitor :: VolumeMonitorClass o => o -> VolumeMonitor
toVolumeMonitor :: forall o. VolumeMonitorClass o => o -> VolumeMonitor
toVolumeMonitor = GObject -> VolumeMonitor
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> VolumeMonitor) -> (o -> GObject) -> o -> VolumeMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance VolumeMonitorClass VolumeMonitor
instance GObjectClass VolumeMonitor where
  toGObject :: VolumeMonitor -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (VolumeMonitor -> ForeignPtr GObject)
-> VolumeMonitor
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr VolumeMonitor -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr VolumeMonitor -> ForeignPtr GObject)
-> (VolumeMonitor -> ForeignPtr VolumeMonitor)
-> VolumeMonitor
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VolumeMonitor -> ForeignPtr VolumeMonitor
unVolumeMonitor
  unsafeCastGObject :: GObject -> VolumeMonitor
unsafeCastGObject = ForeignPtr VolumeMonitor -> VolumeMonitor
VolumeMonitor (ForeignPtr VolumeMonitor -> VolumeMonitor)
-> (GObject -> ForeignPtr VolumeMonitor)
-> GObject
-> VolumeMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr VolumeMonitor
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr VolumeMonitor)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr VolumeMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToVolumeMonitor :: GObjectClass obj => obj -> VolumeMonitor
castToVolumeMonitor :: forall obj. GObjectClass obj => obj -> VolumeMonitor
castToVolumeMonitor = GType -> String -> obj -> VolumeMonitor
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeVolumeMonitor String
"VolumeMonitor"

gTypeVolumeMonitor :: GType
gTypeVolumeMonitor :: GType
gTypeVolumeMonitor =
  GType
g_volume_monitor_get_type
{-# LINE 728 "./System/GIO/Types.chs" #-}

-- **************************************************************** Cancellable

newtype Cancellable = Cancellable (ForeignPtr (Cancellable)) deriving (Cancellable -> Cancellable -> Bool
(Cancellable -> Cancellable -> Bool)
-> (Cancellable -> Cancellable -> Bool) -> Eq Cancellable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cancellable -> Cancellable -> Bool
== :: Cancellable -> Cancellable -> Bool
$c/= :: Cancellable -> Cancellable -> Bool
/= :: Cancellable -> Cancellable -> Bool
Eq,Eq Cancellable
Eq Cancellable =>
(Cancellable -> Cancellable -> Ordering)
-> (Cancellable -> Cancellable -> Bool)
-> (Cancellable -> Cancellable -> Bool)
-> (Cancellable -> Cancellable -> Bool)
-> (Cancellable -> Cancellable -> Bool)
-> (Cancellable -> Cancellable -> Cancellable)
-> (Cancellable -> Cancellable -> Cancellable)
-> Ord Cancellable
Cancellable -> Cancellable -> Bool
Cancellable -> Cancellable -> Ordering
Cancellable -> Cancellable -> Cancellable
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Cancellable -> Cancellable -> Ordering
compare :: Cancellable -> Cancellable -> Ordering
$c< :: Cancellable -> Cancellable -> Bool
< :: Cancellable -> Cancellable -> Bool
$c<= :: Cancellable -> Cancellable -> Bool
<= :: Cancellable -> Cancellable -> Bool
$c> :: Cancellable -> Cancellable -> Bool
> :: Cancellable -> Cancellable -> Bool
$c>= :: Cancellable -> Cancellable -> Bool
>= :: Cancellable -> Cancellable -> Bool
$cmax :: Cancellable -> Cancellable -> Cancellable
max :: Cancellable -> Cancellable -> Cancellable
$cmin :: Cancellable -> Cancellable -> Cancellable
min :: Cancellable -> Cancellable -> Cancellable
Ord)

mkCancellable :: (ForeignPtr Cancellable -> Cancellable, FinalizerPtr a)
mkCancellable = (ForeignPtr Cancellable -> Cancellable
Cancellable, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unCancellable :: Cancellable -> ForeignPtr Cancellable
unCancellable (Cancellable ForeignPtr Cancellable
o) = ForeignPtr Cancellable
o

class GObjectClass o => CancellableClass o
toCancellable :: CancellableClass o => o -> Cancellable
toCancellable :: forall o. CancellableClass o => o -> Cancellable
toCancellable = GObject -> Cancellable
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Cancellable) -> (o -> GObject) -> o -> Cancellable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance CancellableClass Cancellable
instance GObjectClass Cancellable where
  toGObject :: Cancellable -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Cancellable -> ForeignPtr GObject) -> Cancellable -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Cancellable -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Cancellable -> ForeignPtr GObject)
-> (Cancellable -> ForeignPtr Cancellable)
-> Cancellable
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cancellable -> ForeignPtr Cancellable
unCancellable
  unsafeCastGObject :: GObject -> Cancellable
unsafeCastGObject = ForeignPtr Cancellable -> Cancellable
Cancellable (ForeignPtr Cancellable -> Cancellable)
-> (GObject -> ForeignPtr Cancellable) -> GObject -> Cancellable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Cancellable
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Cancellable)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr Cancellable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToCancellable :: GObjectClass obj => obj -> Cancellable
castToCancellable :: forall obj. GObjectClass obj => obj -> Cancellable
castToCancellable = GType -> String -> obj -> Cancellable
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeCancellable String
"Cancellable"

gTypeCancellable :: GType
gTypeCancellable :: GType
gTypeCancellable =
  GType
g_cancellable_get_type
{-# LINE 751 "./System/GIO/Types.chs" #-}

-- ********************************************************** SimpleAsyncResult

newtype SimpleAsyncResult = SimpleAsyncResult (ForeignPtr (SimpleAsyncResult)) deriving (SimpleAsyncResult -> SimpleAsyncResult -> Bool
(SimpleAsyncResult -> SimpleAsyncResult -> Bool)
-> (SimpleAsyncResult -> SimpleAsyncResult -> Bool)
-> Eq SimpleAsyncResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
== :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
$c/= :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
/= :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
Eq,Eq SimpleAsyncResult
Eq SimpleAsyncResult =>
(SimpleAsyncResult -> SimpleAsyncResult -> Ordering)
-> (SimpleAsyncResult -> SimpleAsyncResult -> Bool)
-> (SimpleAsyncResult -> SimpleAsyncResult -> Bool)
-> (SimpleAsyncResult -> SimpleAsyncResult -> Bool)
-> (SimpleAsyncResult -> SimpleAsyncResult -> Bool)
-> (SimpleAsyncResult -> SimpleAsyncResult -> SimpleAsyncResult)
-> (SimpleAsyncResult -> SimpleAsyncResult -> SimpleAsyncResult)
-> Ord SimpleAsyncResult
SimpleAsyncResult -> SimpleAsyncResult -> Bool
SimpleAsyncResult -> SimpleAsyncResult -> Ordering
SimpleAsyncResult -> SimpleAsyncResult -> SimpleAsyncResult
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SimpleAsyncResult -> SimpleAsyncResult -> Ordering
compare :: SimpleAsyncResult -> SimpleAsyncResult -> Ordering
$c< :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
< :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
$c<= :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
<= :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
$c> :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
> :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
$c>= :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
>= :: SimpleAsyncResult -> SimpleAsyncResult -> Bool
$cmax :: SimpleAsyncResult -> SimpleAsyncResult -> SimpleAsyncResult
max :: SimpleAsyncResult -> SimpleAsyncResult -> SimpleAsyncResult
$cmin :: SimpleAsyncResult -> SimpleAsyncResult -> SimpleAsyncResult
min :: SimpleAsyncResult -> SimpleAsyncResult -> SimpleAsyncResult
Ord)

mkSimpleAsyncResult :: (ForeignPtr SimpleAsyncResult -> SimpleAsyncResult, FinalizerPtr a)
mkSimpleAsyncResult = (ForeignPtr SimpleAsyncResult -> SimpleAsyncResult
SimpleAsyncResult, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unSimpleAsyncResult :: SimpleAsyncResult -> ForeignPtr SimpleAsyncResult
unSimpleAsyncResult (SimpleAsyncResult ForeignPtr SimpleAsyncResult
o) = ForeignPtr SimpleAsyncResult
o

class GObjectClass o => SimpleAsyncResultClass o
toSimpleAsyncResult :: SimpleAsyncResultClass o => o -> SimpleAsyncResult
toSimpleAsyncResult :: forall o. SimpleAsyncResultClass o => o -> SimpleAsyncResult
toSimpleAsyncResult = GObject -> SimpleAsyncResult
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> SimpleAsyncResult)
-> (o -> GObject) -> o -> SimpleAsyncResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance SimpleAsyncResultClass SimpleAsyncResult
instance GObjectClass SimpleAsyncResult where
  toGObject :: SimpleAsyncResult -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (SimpleAsyncResult -> ForeignPtr GObject)
-> SimpleAsyncResult
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr SimpleAsyncResult -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr SimpleAsyncResult -> ForeignPtr GObject)
-> (SimpleAsyncResult -> ForeignPtr SimpleAsyncResult)
-> SimpleAsyncResult
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimpleAsyncResult -> ForeignPtr SimpleAsyncResult
unSimpleAsyncResult
  unsafeCastGObject :: GObject -> SimpleAsyncResult
unsafeCastGObject = ForeignPtr SimpleAsyncResult -> SimpleAsyncResult
SimpleAsyncResult (ForeignPtr SimpleAsyncResult -> SimpleAsyncResult)
-> (GObject -> ForeignPtr SimpleAsyncResult)
-> GObject
-> SimpleAsyncResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr SimpleAsyncResult
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr SimpleAsyncResult)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr SimpleAsyncResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToSimpleAsyncResult :: GObjectClass obj => obj -> SimpleAsyncResult
castToSimpleAsyncResult :: forall obj. GObjectClass obj => obj -> SimpleAsyncResult
castToSimpleAsyncResult = GType -> String -> obj -> SimpleAsyncResult
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeSimpleAsyncResult String
"SimpleAsyncResult"

gTypeSimpleAsyncResult :: GType
gTypeSimpleAsyncResult :: GType
gTypeSimpleAsyncResult =
  GType
g_async_result_get_type
{-# LINE 774 "./System/GIO/Types.chs" #-}

-- ******************************************************************* FileInfo

newtype FileInfo = FileInfo (ForeignPtr (FileInfo)) deriving (FileInfo -> FileInfo -> Bool
(FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> Bool) -> Eq FileInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileInfo -> FileInfo -> Bool
== :: FileInfo -> FileInfo -> Bool
$c/= :: FileInfo -> FileInfo -> Bool
/= :: FileInfo -> FileInfo -> Bool
Eq,Eq FileInfo
Eq FileInfo =>
(FileInfo -> FileInfo -> Ordering)
-> (FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> FileInfo)
-> (FileInfo -> FileInfo -> FileInfo)
-> Ord FileInfo
FileInfo -> FileInfo -> Bool
FileInfo -> FileInfo -> Ordering
FileInfo -> FileInfo -> FileInfo
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileInfo -> FileInfo -> Ordering
compare :: FileInfo -> FileInfo -> Ordering
$c< :: FileInfo -> FileInfo -> Bool
< :: FileInfo -> FileInfo -> Bool
$c<= :: FileInfo -> FileInfo -> Bool
<= :: FileInfo -> FileInfo -> Bool
$c> :: FileInfo -> FileInfo -> Bool
> :: FileInfo -> FileInfo -> Bool
$c>= :: FileInfo -> FileInfo -> Bool
>= :: FileInfo -> FileInfo -> Bool
$cmax :: FileInfo -> FileInfo -> FileInfo
max :: FileInfo -> FileInfo -> FileInfo
$cmin :: FileInfo -> FileInfo -> FileInfo
min :: FileInfo -> FileInfo -> FileInfo
Ord)

mkFileInfo :: (ForeignPtr FileInfo -> FileInfo, FinalizerPtr a)
mkFileInfo = (ForeignPtr FileInfo -> FileInfo
FileInfo, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFileInfo :: FileInfo -> ForeignPtr FileInfo
unFileInfo (FileInfo ForeignPtr FileInfo
o) = ForeignPtr FileInfo
o

class GObjectClass o => FileInfoClass o
toFileInfo :: FileInfoClass o => o -> FileInfo
toFileInfo :: forall o. FileInfoClass o => o -> FileInfo
toFileInfo = GObject -> FileInfo
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> FileInfo) -> (o -> GObject) -> o -> FileInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FileInfoClass FileInfo
instance GObjectClass FileInfo where
  toGObject :: FileInfo -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (FileInfo -> ForeignPtr GObject) -> FileInfo -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr FileInfo -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr FileInfo -> ForeignPtr GObject)
-> (FileInfo -> ForeignPtr FileInfo)
-> FileInfo
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileInfo -> ForeignPtr FileInfo
unFileInfo
  unsafeCastGObject :: GObject -> FileInfo
unsafeCastGObject = ForeignPtr FileInfo -> FileInfo
FileInfo (ForeignPtr FileInfo -> FileInfo)
-> (GObject -> ForeignPtr FileInfo) -> GObject -> FileInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr FileInfo
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr FileInfo)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr FileInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFileInfo :: GObjectClass obj => obj -> FileInfo
castToFileInfo :: forall obj. GObjectClass obj => obj -> FileInfo
castToFileInfo = GType -> String -> obj -> FileInfo
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFileInfo String
"FileInfo"

gTypeFileInfo :: GType
gTypeFileInfo :: GType
gTypeFileInfo =
  GType
g_file_info_get_type
{-# LINE 797 "./System/GIO/Types.chs" #-}

-- *********************************************************** AppLaunchContext

newtype AppLaunchContext = AppLaunchContext (ForeignPtr (AppLaunchContext)) deriving (AppLaunchContext -> AppLaunchContext -> Bool
(AppLaunchContext -> AppLaunchContext -> Bool)
-> (AppLaunchContext -> AppLaunchContext -> Bool)
-> Eq AppLaunchContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AppLaunchContext -> AppLaunchContext -> Bool
== :: AppLaunchContext -> AppLaunchContext -> Bool
$c/= :: AppLaunchContext -> AppLaunchContext -> Bool
/= :: AppLaunchContext -> AppLaunchContext -> Bool
Eq,Eq AppLaunchContext
Eq AppLaunchContext =>
(AppLaunchContext -> AppLaunchContext -> Ordering)
-> (AppLaunchContext -> AppLaunchContext -> Bool)
-> (AppLaunchContext -> AppLaunchContext -> Bool)
-> (AppLaunchContext -> AppLaunchContext -> Bool)
-> (AppLaunchContext -> AppLaunchContext -> Bool)
-> (AppLaunchContext -> AppLaunchContext -> AppLaunchContext)
-> (AppLaunchContext -> AppLaunchContext -> AppLaunchContext)
-> Ord AppLaunchContext
AppLaunchContext -> AppLaunchContext -> Bool
AppLaunchContext -> AppLaunchContext -> Ordering
AppLaunchContext -> AppLaunchContext -> AppLaunchContext
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AppLaunchContext -> AppLaunchContext -> Ordering
compare :: AppLaunchContext -> AppLaunchContext -> Ordering
$c< :: AppLaunchContext -> AppLaunchContext -> Bool
< :: AppLaunchContext -> AppLaunchContext -> Bool
$c<= :: AppLaunchContext -> AppLaunchContext -> Bool
<= :: AppLaunchContext -> AppLaunchContext -> Bool
$c> :: AppLaunchContext -> AppLaunchContext -> Bool
> :: AppLaunchContext -> AppLaunchContext -> Bool
$c>= :: AppLaunchContext -> AppLaunchContext -> Bool
>= :: AppLaunchContext -> AppLaunchContext -> Bool
$cmax :: AppLaunchContext -> AppLaunchContext -> AppLaunchContext
max :: AppLaunchContext -> AppLaunchContext -> AppLaunchContext
$cmin :: AppLaunchContext -> AppLaunchContext -> AppLaunchContext
min :: AppLaunchContext -> AppLaunchContext -> AppLaunchContext
Ord)

mkAppLaunchContext :: (ForeignPtr AppLaunchContext -> AppLaunchContext, FinalizerPtr a)
mkAppLaunchContext = (ForeignPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unAppLaunchContext :: AppLaunchContext -> ForeignPtr AppLaunchContext
unAppLaunchContext (AppLaunchContext ForeignPtr AppLaunchContext
o) = ForeignPtr AppLaunchContext
o

class FileInfoClass o => AppLaunchContextClass o
toAppLaunchContext :: AppLaunchContextClass o => o -> AppLaunchContext
toAppLaunchContext :: forall o. AppLaunchContextClass o => o -> AppLaunchContext
toAppLaunchContext = GObject -> AppLaunchContext
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> AppLaunchContext)
-> (o -> GObject) -> o -> AppLaunchContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance AppLaunchContextClass AppLaunchContext
instance FileInfoClass AppLaunchContext
instance GObjectClass AppLaunchContext where
  toGObject :: AppLaunchContext -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (AppLaunchContext -> ForeignPtr GObject)
-> AppLaunchContext
-> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr AppLaunchContext -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr AppLaunchContext -> ForeignPtr GObject)
-> (AppLaunchContext -> ForeignPtr AppLaunchContext)
-> AppLaunchContext
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppLaunchContext -> ForeignPtr AppLaunchContext
unAppLaunchContext
  unsafeCastGObject :: GObject -> AppLaunchContext
unsafeCastGObject = ForeignPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext (ForeignPtr AppLaunchContext -> AppLaunchContext)
-> (GObject -> ForeignPtr AppLaunchContext)
-> GObject
-> AppLaunchContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr AppLaunchContext
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr AppLaunchContext)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr AppLaunchContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToAppLaunchContext :: GObjectClass obj => obj -> AppLaunchContext
castToAppLaunchContext :: forall obj. GObjectClass obj => obj -> AppLaunchContext
castToAppLaunchContext = GType -> String -> obj -> AppLaunchContext
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeAppLaunchContext String
"AppLaunchContext"

gTypeAppLaunchContext :: GType
gTypeAppLaunchContext :: GType
gTypeAppLaunchContext =
  GType
g_app_launch_context_get_type
{-# LINE 821 "./System/GIO/Types.chs" #-}

-- *********************************************************************** Icon

newtype Icon = Icon (ForeignPtr (Icon)) deriving (Icon -> Icon -> Bool
(Icon -> Icon -> Bool) -> (Icon -> Icon -> Bool) -> Eq Icon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Icon -> Icon -> Bool
== :: Icon -> Icon -> Bool
$c/= :: Icon -> Icon -> Bool
/= :: Icon -> Icon -> Bool
Eq,Eq Icon
Eq Icon =>
(Icon -> Icon -> Ordering)
-> (Icon -> Icon -> Bool)
-> (Icon -> Icon -> Bool)
-> (Icon -> Icon -> Bool)
-> (Icon -> Icon -> Bool)
-> (Icon -> Icon -> Icon)
-> (Icon -> Icon -> Icon)
-> Ord Icon
Icon -> Icon -> Bool
Icon -> Icon -> Ordering
Icon -> Icon -> Icon
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Icon -> Icon -> Ordering
compare :: Icon -> Icon -> Ordering
$c< :: Icon -> Icon -> Bool
< :: Icon -> Icon -> Bool
$c<= :: Icon -> Icon -> Bool
<= :: Icon -> Icon -> Bool
$c> :: Icon -> Icon -> Bool
> :: Icon -> Icon -> Bool
$c>= :: Icon -> Icon -> Bool
>= :: Icon -> Icon -> Bool
$cmax :: Icon -> Icon -> Icon
max :: Icon -> Icon -> Icon
$cmin :: Icon -> Icon -> Icon
min :: Icon -> Icon -> Icon
Ord)

mkIcon :: (ForeignPtr Icon -> Icon, FinalizerPtr a)
mkIcon = (ForeignPtr Icon -> Icon
Icon, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unIcon :: Icon -> ForeignPtr Icon
unIcon (Icon ForeignPtr Icon
o) = ForeignPtr Icon
o

class GObjectClass o => IconClass o
toIcon :: IconClass o => o -> Icon
toIcon :: forall o. IconClass o => o -> Icon
toIcon = GObject -> Icon
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Icon) -> (o -> GObject) -> o -> Icon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance IconClass Icon
instance GObjectClass Icon where
  toGObject :: Icon -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Icon -> ForeignPtr GObject) -> Icon -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Icon -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Icon -> ForeignPtr GObject)
-> (Icon -> ForeignPtr Icon) -> Icon -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Icon -> ForeignPtr Icon
unIcon
  unsafeCastGObject :: GObject -> Icon
unsafeCastGObject = ForeignPtr Icon -> Icon
Icon (ForeignPtr Icon -> Icon)
-> (GObject -> ForeignPtr Icon) -> GObject -> Icon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Icon
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Icon)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr Icon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToIcon :: GObjectClass obj => obj -> Icon
castToIcon :: forall obj. GObjectClass obj => obj -> Icon
castToIcon = GType -> String -> obj -> Icon
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeIcon String
"Icon"

gTypeIcon :: GType
gTypeIcon :: GType
gTypeIcon =
  GType
g_icon_get_type
{-# LINE 844 "./System/GIO/Types.chs" #-}

-- ******************************************************************* Seekable

newtype Seekable = Seekable (ForeignPtr (Seekable)) deriving (Seekable -> Seekable -> Bool
(Seekable -> Seekable -> Bool)
-> (Seekable -> Seekable -> Bool) -> Eq Seekable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Seekable -> Seekable -> Bool
== :: Seekable -> Seekable -> Bool
$c/= :: Seekable -> Seekable -> Bool
/= :: Seekable -> Seekable -> Bool
Eq,Eq Seekable
Eq Seekable =>
(Seekable -> Seekable -> Ordering)
-> (Seekable -> Seekable -> Bool)
-> (Seekable -> Seekable -> Bool)
-> (Seekable -> Seekable -> Bool)
-> (Seekable -> Seekable -> Bool)
-> (Seekable -> Seekable -> Seekable)
-> (Seekable -> Seekable -> Seekable)
-> Ord Seekable
Seekable -> Seekable -> Bool
Seekable -> Seekable -> Ordering
Seekable -> Seekable -> Seekable
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Seekable -> Seekable -> Ordering
compare :: Seekable -> Seekable -> Ordering
$c< :: Seekable -> Seekable -> Bool
< :: Seekable -> Seekable -> Bool
$c<= :: Seekable -> Seekable -> Bool
<= :: Seekable -> Seekable -> Bool
$c> :: Seekable -> Seekable -> Bool
> :: Seekable -> Seekable -> Bool
$c>= :: Seekable -> Seekable -> Bool
>= :: Seekable -> Seekable -> Bool
$cmax :: Seekable -> Seekable -> Seekable
max :: Seekable -> Seekable -> Seekable
$cmin :: Seekable -> Seekable -> Seekable
min :: Seekable -> Seekable -> Seekable
Ord)

mkSeekable :: (ForeignPtr Seekable -> Seekable, FinalizerPtr a)
mkSeekable = (ForeignPtr Seekable -> Seekable
Seekable, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unSeekable :: Seekable -> ForeignPtr Seekable
unSeekable (Seekable ForeignPtr Seekable
o) = ForeignPtr Seekable
o

class GObjectClass o => SeekableClass o
toSeekable :: SeekableClass o => o -> Seekable
toSeekable :: forall o. SeekableClass o => o -> Seekable
toSeekable = GObject -> Seekable
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Seekable) -> (o -> GObject) -> o -> Seekable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance SeekableClass Seekable
instance GObjectClass Seekable where
  toGObject :: Seekable -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Seekable -> ForeignPtr GObject) -> Seekable -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Seekable -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Seekable -> ForeignPtr GObject)
-> (Seekable -> ForeignPtr Seekable)
-> Seekable
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seekable -> ForeignPtr Seekable
unSeekable
  unsafeCastGObject :: GObject -> Seekable
unsafeCastGObject = ForeignPtr Seekable -> Seekable
Seekable (ForeignPtr Seekable -> Seekable)
-> (GObject -> ForeignPtr Seekable) -> GObject -> Seekable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Seekable
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Seekable)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr Seekable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToSeekable :: GObjectClass obj => obj -> Seekable
castToSeekable :: forall obj. GObjectClass obj => obj -> Seekable
castToSeekable = GType -> String -> obj -> Seekable
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeSeekable String
"Seekable"

gTypeSeekable :: GType
gTypeSeekable :: GType
gTypeSeekable =
  GType
g_seekable_get_type
{-# LINE 867 "./System/GIO/Types.chs" #-}

-- ******************************************************************** AppInfo

newtype AppInfo = AppInfo (ForeignPtr (AppInfo)) deriving (AppInfo -> AppInfo -> Bool
(AppInfo -> AppInfo -> Bool)
-> (AppInfo -> AppInfo -> Bool) -> Eq AppInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AppInfo -> AppInfo -> Bool
== :: AppInfo -> AppInfo -> Bool
$c/= :: AppInfo -> AppInfo -> Bool
/= :: AppInfo -> AppInfo -> Bool
Eq,Eq AppInfo
Eq AppInfo =>
(AppInfo -> AppInfo -> Ordering)
-> (AppInfo -> AppInfo -> Bool)
-> (AppInfo -> AppInfo -> Bool)
-> (AppInfo -> AppInfo -> Bool)
-> (AppInfo -> AppInfo -> Bool)
-> (AppInfo -> AppInfo -> AppInfo)
-> (AppInfo -> AppInfo -> AppInfo)
-> Ord AppInfo
AppInfo -> AppInfo -> Bool
AppInfo -> AppInfo -> Ordering
AppInfo -> AppInfo -> AppInfo
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AppInfo -> AppInfo -> Ordering
compare :: AppInfo -> AppInfo -> Ordering
$c< :: AppInfo -> AppInfo -> Bool
< :: AppInfo -> AppInfo -> Bool
$c<= :: AppInfo -> AppInfo -> Bool
<= :: AppInfo -> AppInfo -> Bool
$c> :: AppInfo -> AppInfo -> Bool
> :: AppInfo -> AppInfo -> Bool
$c>= :: AppInfo -> AppInfo -> Bool
>= :: AppInfo -> AppInfo -> Bool
$cmax :: AppInfo -> AppInfo -> AppInfo
max :: AppInfo -> AppInfo -> AppInfo
$cmin :: AppInfo -> AppInfo -> AppInfo
min :: AppInfo -> AppInfo -> AppInfo
Ord)

mkAppInfo :: (ForeignPtr AppInfo -> AppInfo, FinalizerPtr a)
mkAppInfo = (ForeignPtr AppInfo -> AppInfo
AppInfo, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unAppInfo :: AppInfo -> ForeignPtr AppInfo
unAppInfo (AppInfo ForeignPtr AppInfo
o) = ForeignPtr AppInfo
o

class GObjectClass o => AppInfoClass o
toAppInfo :: AppInfoClass o => o -> AppInfo
toAppInfo :: forall o. AppInfoClass o => o -> AppInfo
toAppInfo = GObject -> AppInfo
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> AppInfo) -> (o -> GObject) -> o -> AppInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance AppInfoClass AppInfo
instance GObjectClass AppInfo where
  toGObject :: AppInfo -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (AppInfo -> ForeignPtr GObject) -> AppInfo -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr AppInfo -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr AppInfo -> ForeignPtr GObject)
-> (AppInfo -> ForeignPtr AppInfo) -> AppInfo -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppInfo -> ForeignPtr AppInfo
unAppInfo
  unsafeCastGObject :: GObject -> AppInfo
unsafeCastGObject = ForeignPtr AppInfo -> AppInfo
AppInfo (ForeignPtr AppInfo -> AppInfo)
-> (GObject -> ForeignPtr AppInfo) -> GObject -> AppInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr AppInfo
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr AppInfo)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr AppInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToAppInfo :: GObjectClass obj => obj -> AppInfo
castToAppInfo :: forall obj. GObjectClass obj => obj -> AppInfo
castToAppInfo = GType -> String -> obj -> AppInfo
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeAppInfo String
"AppInfo"

gTypeAppInfo :: GType
gTypeAppInfo :: GType
gTypeAppInfo =
  GType
g_app_info_get_type
{-# LINE 890 "./System/GIO/Types.chs" #-}

-- ********************************************************************* Volume

newtype Volume = Volume (ForeignPtr (Volume)) deriving (Volume -> Volume -> Bool
(Volume -> Volume -> Bool)
-> (Volume -> Volume -> Bool) -> Eq Volume
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Volume -> Volume -> Bool
== :: Volume -> Volume -> Bool
$c/= :: Volume -> Volume -> Bool
/= :: Volume -> Volume -> Bool
Eq,Eq Volume
Eq Volume =>
(Volume -> Volume -> Ordering)
-> (Volume -> Volume -> Bool)
-> (Volume -> Volume -> Bool)
-> (Volume -> Volume -> Bool)
-> (Volume -> Volume -> Bool)
-> (Volume -> Volume -> Volume)
-> (Volume -> Volume -> Volume)
-> Ord Volume
Volume -> Volume -> Bool
Volume -> Volume -> Ordering
Volume -> Volume -> Volume
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Volume -> Volume -> Ordering
compare :: Volume -> Volume -> Ordering
$c< :: Volume -> Volume -> Bool
< :: Volume -> Volume -> Bool
$c<= :: Volume -> Volume -> Bool
<= :: Volume -> Volume -> Bool
$c> :: Volume -> Volume -> Bool
> :: Volume -> Volume -> Bool
$c>= :: Volume -> Volume -> Bool
>= :: Volume -> Volume -> Bool
$cmax :: Volume -> Volume -> Volume
max :: Volume -> Volume -> Volume
$cmin :: Volume -> Volume -> Volume
min :: Volume -> Volume -> Volume
Ord)

mkVolume :: (ForeignPtr Volume -> Volume, FinalizerPtr a)
mkVolume = (ForeignPtr Volume -> Volume
Volume, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unVolume :: Volume -> ForeignPtr Volume
unVolume (Volume ForeignPtr Volume
o) = ForeignPtr Volume
o

class GObjectClass o => VolumeClass o
toVolume :: VolumeClass o => o -> Volume
toVolume :: forall o. VolumeClass o => o -> Volume
toVolume = GObject -> Volume
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Volume) -> (o -> GObject) -> o -> Volume
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance VolumeClass Volume
instance GObjectClass Volume where
  toGObject :: Volume -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Volume -> ForeignPtr GObject) -> Volume -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Volume -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Volume -> ForeignPtr GObject)
-> (Volume -> ForeignPtr Volume) -> Volume -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Volume -> ForeignPtr Volume
unVolume
  unsafeCastGObject :: GObject -> Volume
unsafeCastGObject = ForeignPtr Volume -> Volume
Volume (ForeignPtr Volume -> Volume)
-> (GObject -> ForeignPtr Volume) -> GObject -> Volume
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Volume
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Volume)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr Volume
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToVolume :: GObjectClass obj => obj -> Volume
castToVolume :: forall obj. GObjectClass obj => obj -> Volume
castToVolume = GType -> String -> obj -> Volume
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeVolume String
"Volume"

gTypeVolume :: GType
gTypeVolume :: GType
gTypeVolume =
  GType
g_volume_get_type
{-# LINE 913 "./System/GIO/Types.chs" #-}

-- **************************************************************** AsyncResult

newtype AsyncResult = AsyncResult (ForeignPtr (AsyncResult)) deriving (AsyncResult -> AsyncResult -> Bool
(AsyncResult -> AsyncResult -> Bool)
-> (AsyncResult -> AsyncResult -> Bool) -> Eq AsyncResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AsyncResult -> AsyncResult -> Bool
== :: AsyncResult -> AsyncResult -> Bool
$c/= :: AsyncResult -> AsyncResult -> Bool
/= :: AsyncResult -> AsyncResult -> Bool
Eq,Eq AsyncResult
Eq AsyncResult =>
(AsyncResult -> AsyncResult -> Ordering)
-> (AsyncResult -> AsyncResult -> Bool)
-> (AsyncResult -> AsyncResult -> Bool)
-> (AsyncResult -> AsyncResult -> Bool)
-> (AsyncResult -> AsyncResult -> Bool)
-> (AsyncResult -> AsyncResult -> AsyncResult)
-> (AsyncResult -> AsyncResult -> AsyncResult)
-> Ord AsyncResult
AsyncResult -> AsyncResult -> Bool
AsyncResult -> AsyncResult -> Ordering
AsyncResult -> AsyncResult -> AsyncResult
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AsyncResult -> AsyncResult -> Ordering
compare :: AsyncResult -> AsyncResult -> Ordering
$c< :: AsyncResult -> AsyncResult -> Bool
< :: AsyncResult -> AsyncResult -> Bool
$c<= :: AsyncResult -> AsyncResult -> Bool
<= :: AsyncResult -> AsyncResult -> Bool
$c> :: AsyncResult -> AsyncResult -> Bool
> :: AsyncResult -> AsyncResult -> Bool
$c>= :: AsyncResult -> AsyncResult -> Bool
>= :: AsyncResult -> AsyncResult -> Bool
$cmax :: AsyncResult -> AsyncResult -> AsyncResult
max :: AsyncResult -> AsyncResult -> AsyncResult
$cmin :: AsyncResult -> AsyncResult -> AsyncResult
min :: AsyncResult -> AsyncResult -> AsyncResult
Ord)

mkAsyncResult :: (ForeignPtr AsyncResult -> AsyncResult, FinalizerPtr a)
mkAsyncResult = (ForeignPtr AsyncResult -> AsyncResult
AsyncResult, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unAsyncResult :: AsyncResult -> ForeignPtr AsyncResult
unAsyncResult (AsyncResult ForeignPtr AsyncResult
o) = ForeignPtr AsyncResult
o

class GObjectClass o => AsyncResultClass o
toAsyncResult :: AsyncResultClass o => o -> AsyncResult
toAsyncResult :: forall o. AsyncResultClass o => o -> AsyncResult
toAsyncResult = GObject -> AsyncResult
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> AsyncResult) -> (o -> GObject) -> o -> AsyncResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance AsyncResultClass AsyncResult
instance GObjectClass AsyncResult where
  toGObject :: AsyncResult -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (AsyncResult -> ForeignPtr GObject) -> AsyncResult -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr AsyncResult -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr AsyncResult -> ForeignPtr GObject)
-> (AsyncResult -> ForeignPtr AsyncResult)
-> AsyncResult
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AsyncResult -> ForeignPtr AsyncResult
unAsyncResult
  unsafeCastGObject :: GObject -> AsyncResult
unsafeCastGObject = ForeignPtr AsyncResult -> AsyncResult
AsyncResult (ForeignPtr AsyncResult -> AsyncResult)
-> (GObject -> ForeignPtr AsyncResult) -> GObject -> AsyncResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr AsyncResult
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr AsyncResult)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr AsyncResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToAsyncResult :: GObjectClass obj => obj -> AsyncResult
castToAsyncResult :: forall obj. GObjectClass obj => obj -> AsyncResult
castToAsyncResult = GType -> String -> obj -> AsyncResult
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeAsyncResult String
"AsyncResult"

gTypeAsyncResult :: GType
gTypeAsyncResult :: GType
gTypeAsyncResult =
  GType
g_async_result_get_type
{-# LINE 936 "./System/GIO/Types.chs" #-}

-- *************************************************************** LoadableIcon

newtype LoadableIcon = LoadableIcon (ForeignPtr (LoadableIcon)) deriving (LoadableIcon -> LoadableIcon -> Bool
(LoadableIcon -> LoadableIcon -> Bool)
-> (LoadableIcon -> LoadableIcon -> Bool) -> Eq LoadableIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LoadableIcon -> LoadableIcon -> Bool
== :: LoadableIcon -> LoadableIcon -> Bool
$c/= :: LoadableIcon -> LoadableIcon -> Bool
/= :: LoadableIcon -> LoadableIcon -> Bool
Eq,Eq LoadableIcon
Eq LoadableIcon =>
(LoadableIcon -> LoadableIcon -> Ordering)
-> (LoadableIcon -> LoadableIcon -> Bool)
-> (LoadableIcon -> LoadableIcon -> Bool)
-> (LoadableIcon -> LoadableIcon -> Bool)
-> (LoadableIcon -> LoadableIcon -> Bool)
-> (LoadableIcon -> LoadableIcon -> LoadableIcon)
-> (LoadableIcon -> LoadableIcon -> LoadableIcon)
-> Ord LoadableIcon
LoadableIcon -> LoadableIcon -> Bool
LoadableIcon -> LoadableIcon -> Ordering
LoadableIcon -> LoadableIcon -> LoadableIcon
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LoadableIcon -> LoadableIcon -> Ordering
compare :: LoadableIcon -> LoadableIcon -> Ordering
$c< :: LoadableIcon -> LoadableIcon -> Bool
< :: LoadableIcon -> LoadableIcon -> Bool
$c<= :: LoadableIcon -> LoadableIcon -> Bool
<= :: LoadableIcon -> LoadableIcon -> Bool
$c> :: LoadableIcon -> LoadableIcon -> Bool
> :: LoadableIcon -> LoadableIcon -> Bool
$c>= :: LoadableIcon -> LoadableIcon -> Bool
>= :: LoadableIcon -> LoadableIcon -> Bool
$cmax :: LoadableIcon -> LoadableIcon -> LoadableIcon
max :: LoadableIcon -> LoadableIcon -> LoadableIcon
$cmin :: LoadableIcon -> LoadableIcon -> LoadableIcon
min :: LoadableIcon -> LoadableIcon -> LoadableIcon
Ord)

mkLoadableIcon :: (ForeignPtr LoadableIcon -> LoadableIcon, FinalizerPtr a)
mkLoadableIcon = (ForeignPtr LoadableIcon -> LoadableIcon
LoadableIcon, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unLoadableIcon :: LoadableIcon -> ForeignPtr LoadableIcon
unLoadableIcon (LoadableIcon ForeignPtr LoadableIcon
o) = ForeignPtr LoadableIcon
o

class GObjectClass o => LoadableIconClass o
toLoadableIcon :: LoadableIconClass o => o -> LoadableIcon
toLoadableIcon :: forall o. LoadableIconClass o => o -> LoadableIcon
toLoadableIcon = GObject -> LoadableIcon
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> LoadableIcon) -> (o -> GObject) -> o -> LoadableIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance LoadableIconClass LoadableIcon
instance GObjectClass LoadableIcon where
  toGObject :: LoadableIcon -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (LoadableIcon -> ForeignPtr GObject) -> LoadableIcon -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr LoadableIcon -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr LoadableIcon -> ForeignPtr GObject)
-> (LoadableIcon -> ForeignPtr LoadableIcon)
-> LoadableIcon
-> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LoadableIcon -> ForeignPtr LoadableIcon
unLoadableIcon
  unsafeCastGObject :: GObject -> LoadableIcon
unsafeCastGObject = ForeignPtr LoadableIcon -> LoadableIcon
LoadableIcon (ForeignPtr LoadableIcon -> LoadableIcon)
-> (GObject -> ForeignPtr LoadableIcon) -> GObject -> LoadableIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr LoadableIcon
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr LoadableIcon)
-> (GObject -> ForeignPtr GObject)
-> GObject
-> ForeignPtr LoadableIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToLoadableIcon :: GObjectClass obj => obj -> LoadableIcon
castToLoadableIcon :: forall obj. GObjectClass obj => obj -> LoadableIcon
castToLoadableIcon = GType -> String -> obj -> LoadableIcon
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeLoadableIcon String
"LoadableIcon"

gTypeLoadableIcon :: GType
gTypeLoadableIcon :: GType
gTypeLoadableIcon =
  GType
g_loadable_icon_get_type
{-# LINE 959 "./System/GIO/Types.chs" #-}

-- ********************************************************************** Drive

newtype Drive = Drive (ForeignPtr (Drive)) deriving (Drive -> Drive -> Bool
(Drive -> Drive -> Bool) -> (Drive -> Drive -> Bool) -> Eq Drive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Drive -> Drive -> Bool
== :: Drive -> Drive -> Bool
$c/= :: Drive -> Drive -> Bool
/= :: Drive -> Drive -> Bool
Eq,Eq Drive
Eq Drive =>
(Drive -> Drive -> Ordering)
-> (Drive -> Drive -> Bool)
-> (Drive -> Drive -> Bool)
-> (Drive -> Drive -> Bool)
-> (Drive -> Drive -> Bool)
-> (Drive -> Drive -> Drive)
-> (Drive -> Drive -> Drive)
-> Ord Drive
Drive -> Drive -> Bool
Drive -> Drive -> Ordering
Drive -> Drive -> Drive
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Drive -> Drive -> Ordering
compare :: Drive -> Drive -> Ordering
$c< :: Drive -> Drive -> Bool
< :: Drive -> Drive -> Bool
$c<= :: Drive -> Drive -> Bool
<= :: Drive -> Drive -> Bool
$c> :: Drive -> Drive -> Bool
> :: Drive -> Drive -> Bool
$c>= :: Drive -> Drive -> Bool
>= :: Drive -> Drive -> Bool
$cmax :: Drive -> Drive -> Drive
max :: Drive -> Drive -> Drive
$cmin :: Drive -> Drive -> Drive
min :: Drive -> Drive -> Drive
Ord)

mkDrive :: (ForeignPtr Drive -> Drive, FinalizerPtr a)
mkDrive = (ForeignPtr Drive -> Drive
Drive, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unDrive :: Drive -> ForeignPtr Drive
unDrive (Drive ForeignPtr Drive
o) = ForeignPtr Drive
o

class GObjectClass o => DriveClass o
toDrive :: DriveClass o => o -> Drive
toDrive :: forall o. DriveClass o => o -> Drive
toDrive = GObject -> Drive
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Drive) -> (o -> GObject) -> o -> Drive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance DriveClass Drive
instance GObjectClass Drive where
  toGObject :: Drive -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Drive -> ForeignPtr GObject) -> Drive -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Drive -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Drive -> ForeignPtr GObject)
-> (Drive -> ForeignPtr Drive) -> Drive -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Drive -> ForeignPtr Drive
unDrive
  unsafeCastGObject :: GObject -> Drive
unsafeCastGObject = ForeignPtr Drive -> Drive
Drive (ForeignPtr Drive -> Drive)
-> (GObject -> ForeignPtr Drive) -> GObject -> Drive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Drive
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Drive)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr Drive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToDrive :: GObjectClass obj => obj -> Drive
castToDrive :: forall obj. GObjectClass obj => obj -> Drive
castToDrive = GType -> String -> obj -> Drive
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeDrive String
"Drive"

gTypeDrive :: GType
gTypeDrive :: GType
gTypeDrive =
  GType
g_drive_get_type
{-# LINE 982 "./System/GIO/Types.chs" #-}

-- *********************************************************************** File

newtype File = File (ForeignPtr (File))
{-# LINE 986 "./System/GIO/Types.chs" #-}

mkFile :: (ForeignPtr File -> File, FinalizerPtr a)
mkFile = (ForeignPtr File -> File
File, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unFile :: File -> ForeignPtr File
unFile (File ForeignPtr File
o) = ForeignPtr File
o

class GObjectClass o => FileClass o
toFile :: FileClass o => o -> File
toFile :: forall o. FileClass o => o -> File
toFile = GObject -> File
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> File) -> (o -> GObject) -> o -> File
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance FileClass File
instance GObjectClass File where
  toGObject :: File -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (File -> ForeignPtr GObject) -> File -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr File -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr File -> ForeignPtr GObject)
-> (File -> ForeignPtr File) -> File -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. File -> ForeignPtr File
unFile
  unsafeCastGObject :: GObject -> File
unsafeCastGObject = ForeignPtr File -> File
File (ForeignPtr File -> File)
-> (GObject -> ForeignPtr File) -> GObject -> File
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr File
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr File)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr File
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToFile :: GObjectClass obj => obj -> File
castToFile :: forall obj. GObjectClass obj => obj -> File
castToFile = GType -> String -> obj -> File
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeFile String
"File"

gTypeFile :: GType
gTypeFile :: GType
gTypeFile =
  GType
g_file_get_type
{-# LINE 1005 "./System/GIO/Types.chs" #-}

-- ********************************************************************** Mount

newtype Mount = Mount (ForeignPtr (Mount)) deriving (Mount -> Mount -> Bool
(Mount -> Mount -> Bool) -> (Mount -> Mount -> Bool) -> Eq Mount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Mount -> Mount -> Bool
== :: Mount -> Mount -> Bool
$c/= :: Mount -> Mount -> Bool
/= :: Mount -> Mount -> Bool
Eq,Eq Mount
Eq Mount =>
(Mount -> Mount -> Ordering)
-> (Mount -> Mount -> Bool)
-> (Mount -> Mount -> Bool)
-> (Mount -> Mount -> Bool)
-> (Mount -> Mount -> Bool)
-> (Mount -> Mount -> Mount)
-> (Mount -> Mount -> Mount)
-> Ord Mount
Mount -> Mount -> Bool
Mount -> Mount -> Ordering
Mount -> Mount -> Mount
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Mount -> Mount -> Ordering
compare :: Mount -> Mount -> Ordering
$c< :: Mount -> Mount -> Bool
< :: Mount -> Mount -> Bool
$c<= :: Mount -> Mount -> Bool
<= :: Mount -> Mount -> Bool
$c> :: Mount -> Mount -> Bool
> :: Mount -> Mount -> Bool
$c>= :: Mount -> Mount -> Bool
>= :: Mount -> Mount -> Bool
$cmax :: Mount -> Mount -> Mount
max :: Mount -> Mount -> Mount
$cmin :: Mount -> Mount -> Mount
min :: Mount -> Mount -> Mount
Ord)

mkMount :: (ForeignPtr Mount -> Mount, FinalizerPtr a)
mkMount = (ForeignPtr Mount -> Mount
Mount, FinalizerPtr a
forall a. FinalizerPtr a
objectUnref)
unMount :: Mount -> ForeignPtr Mount
unMount (Mount ForeignPtr Mount
o) = ForeignPtr Mount
o

class GObjectClass o => MountClass o
toMount :: MountClass o => o -> Mount
toMount :: forall o. MountClass o => o -> Mount
toMount = GObject -> Mount
forall o. GObjectClass o => GObject -> o
unsafeCastGObject (GObject -> Mount) -> (o -> GObject) -> o -> Mount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> GObject
forall o. GObjectClass o => o -> GObject
toGObject

instance MountClass Mount
instance GObjectClass Mount where
  toGObject :: Mount -> GObject
toGObject = ForeignPtr GObject -> GObject
GObject (ForeignPtr GObject -> GObject)
-> (Mount -> ForeignPtr GObject) -> Mount -> GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr Mount -> ForeignPtr GObject
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr Mount -> ForeignPtr GObject)
-> (Mount -> ForeignPtr Mount) -> Mount -> ForeignPtr GObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Mount -> ForeignPtr Mount
unMount
  unsafeCastGObject :: GObject -> Mount
unsafeCastGObject = ForeignPtr Mount -> Mount
Mount (ForeignPtr Mount -> Mount)
-> (GObject -> ForeignPtr Mount) -> GObject -> Mount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr GObject -> ForeignPtr Mount
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr GObject -> ForeignPtr Mount)
-> (GObject -> ForeignPtr GObject) -> GObject -> ForeignPtr Mount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GObject -> ForeignPtr GObject
unGObject

castToMount :: GObjectClass obj => obj -> Mount
castToMount :: forall obj. GObjectClass obj => obj -> Mount
castToMount = GType -> String -> obj -> Mount
forall obj obj'.
(GObjectClass obj, GObjectClass obj') =>
GType -> String -> obj -> obj'
castTo GType
gTypeMount String
"Mount"

gTypeMount :: GType
gTypeMount :: GType
gTypeMount =
  GType
g_mount_get_type
{-# LINE 1028 "./System/GIO/Types.chs" #-}

foreign import ccall unsafe "g_output_stream_get_type"
  g_output_stream_get_type :: CULong

foreign import ccall unsafe "g_filter_output_stream_get_type"
  g_filter_output_stream_get_type :: CULong

foreign import ccall unsafe "g_data_output_stream_get_type"
  g_data_output_stream_get_type :: CULong

foreign import ccall unsafe "g_buffered_output_stream_get_type"
  g_buffered_output_stream_get_type :: CULong

foreign import ccall unsafe "g_file_output_stream_get_type"
  g_file_output_stream_get_type :: CULong

foreign import ccall unsafe "g_memory_output_stream_get_type"
  g_memory_output_stream_get_type :: CULong

foreign import ccall unsafe "g_input_stream_get_type"
  g_input_stream_get_type :: CULong

foreign import ccall unsafe "g_memory_input_stream_get_type"
  g_memory_input_stream_get_type :: CULong

foreign import ccall unsafe "g_filter_input_stream_get_type"
  g_filter_input_stream_get_type :: CULong

foreign import ccall unsafe "g_buffered_input_stream_get_type"
  g_buffered_input_stream_get_type :: CULong

foreign import ccall unsafe "g_data_input_stream_get_type"
  g_data_input_stream_get_type :: CULong

foreign import ccall unsafe "g_file_input_stream_get_type"
  g_file_input_stream_get_type :: CULong

foreign import ccall unsafe "g_file_monitor_get_type"
  g_file_monitor_get_type :: CULong

foreign import ccall unsafe "g_vfs_get_type"
  g_vfs_get_type :: CULong

foreign import ccall unsafe "g_mount_operation_get_type"
  g_mount_operation_get_type :: CULong

foreign import ccall unsafe "g_themed_icon_get_type"
  g_themed_icon_get_type :: CULong

foreign import ccall unsafe "g_emblem_get_type"
  g_emblem_get_type :: CULong

foreign import ccall unsafe "g_emblemed_icon_get_type"
  g_emblemed_icon_get_type :: CULong

foreign import ccall unsafe "g_file_enumerator_get_type"
  g_file_enumerator_get_type :: CULong

foreign import ccall unsafe "g_filename_completer_get_type"
  g_filename_completer_get_type :: CULong

foreign import ccall unsafe "g_file_icon_get_type"
  g_file_icon_get_type :: CULong

foreign import ccall unsafe "g_volume_monitor_get_type"
  g_volume_monitor_get_type :: CULong

foreign import ccall unsafe "g_cancellable_get_type"
  g_cancellable_get_type :: CULong

foreign import ccall unsafe "g_async_result_get_type"
  g_async_result_get_type :: CULong

foreign import ccall unsafe "g_file_info_get_type"
  g_file_info_get_type :: CULong

foreign import ccall unsafe "g_app_launch_context_get_type"
  g_app_launch_context_get_type :: CULong

foreign import ccall unsafe "g_icon_get_type"
  g_icon_get_type :: CULong

foreign import ccall unsafe "g_seekable_get_type"
  g_seekable_get_type :: CULong

foreign import ccall unsafe "g_app_info_get_type"
  g_app_info_get_type :: CULong

foreign import ccall unsafe "g_volume_get_type"
  g_volume_get_type :: CULong

foreign import ccall unsafe "g_loadable_icon_get_type"
  g_loadable_icon_get_type :: CULong

foreign import ccall unsafe "g_drive_get_type"
  g_drive_get_type :: CULong

foreign import ccall unsafe "g_file_get_type"
  g_file_get_type :: CULong

foreign import ccall unsafe "g_mount_get_type"
  g_mount_get_type :: CULong