{-# LINE 2 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
module Graphics.UI.Gtk.Selectors.FileChooser (
  FileChooser,
  FileChooserClass,
  castToFileChooser, gTypeFileChooser,
  toFileChooser,
  FileChooserAction(..),
  FileChooserError(..),
  FileChooserConfirmation(..),
  fileChooserSetAction,
  fileChooserGetAction,
  fileChooserSetLocalOnly,
  fileChooserGetLocalOnly,
  fileChooserSetSelectMultiple,
  fileChooserGetSelectMultiple,
  fileChooserSetCurrentName,
  fileChooserGetFilename,
  fileChooserSetFilename,
  fileChooserSelectFilename,
  fileChooserUnselectFilename,
  fileChooserSelectAll,
  fileChooserUnselectAll,
  fileChooserGetFilenames,
  fileChooserSetCurrentFolder,
  fileChooserGetCurrentFolder,
  fileChooserGetURI,
  fileChooserSetURI,
  fileChooserSelectURI,
  fileChooserUnselectURI,
  fileChooserGetURIs,
  fileChooserSetCurrentFolderURI,
  fileChooserGetCurrentFolderURI,
  fileChooserSetPreviewWidget,
  fileChooserGetPreviewWidget,
  fileChooserSetPreviewWidgetActive,
  fileChooserGetPreviewWidgetActive,
  fileChooserSetUsePreviewLabel,
  fileChooserGetUsePreviewLabel,
  fileChooserGetPreviewFilename,
  fileChooserGetPreviewURI,
  fileChooserSetExtraWidget,
  fileChooserGetExtraWidget,
  fileChooserAddFilter,
  fileChooserRemoveFilter,
  fileChooserListFilters,
  fileChooserSetFilter,
  fileChooserGetFilter,
  fileChooserAddShortcutFolder,
  fileChooserRemoveShortcutFolder,
  fileChooserListShortcutFolders,
  fileChooserAddShortcutFolderURI,
  fileChooserRemoveShortcutFolderURI,
  fileChooserListShortcutFolderURIs,
  fileChooserErrorDomain,
  fileChooserSetShowHidden,
  fileChooserGetShowHidden,
  fileChooserSetDoOverwriteConfirmation,
  fileChooserGetDoOverwriteConfirmation,
  fileChooserUsePreviewLabel,
  fileChooserShowHidden,
  fileChooserSelectMultiple,
  fileChooserPreviewWidgetActive,
  fileChooserPreviewWidget,
  fileChooserLocalOnly,
  fileChooserFilter,
  fileChooserExtraWidget,
  fileChooserDoOverwriteConfirmation,
  fileChooserAction,
  currentFolderChanged,
  fileActivated,
  fileSelectionChanged,
  updatePreview,
  confirmOverwrite,
  onCurrentFolderChanged,
  afterCurrentFolderChanged,
  onFileActivated,
  afterFileActivated,
  onUpdatePreview,
  afterUpdatePreview,
  onConfirmOverwrite,
  afterConfirmOverwrite,
  ) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import Graphics.UI.Gtk.Types
{-# LINE 242 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Signals
import System.Glib.GList
{-# LINE 245 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
import System.Glib.GError (propagateGError, GErrorDomain, GErrorClass(..))
{-# LINE 248 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
data FileChooserAction = FileChooserActionOpen
                       | FileChooserActionSave
                       | FileChooserActionSelectFolder
                       | FileChooserActionCreateFolder
                       deriving (Enum)
{-# LINE 254 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
data FileChooserError = FileChooserErrorNonexistent
                      | FileChooserErrorBadFilename
                      | FileChooserErrorAlreadyExists
                      | FileChooserErrorIncompleteHostname
                      deriving (Enum)
{-# LINE 258 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
data FileChooserConfirmation = FileChooserConfirmationConfirm
                             | FileChooserConfirmationAcceptFilename
                             | FileChooserConfirmationSelectAgain
                             deriving (Enum)
{-# LINE 271 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
fileChooserErrorDomain :: GErrorDomain
fileChooserErrorDomain = unsafePerformIO gtk_file_chooser_error_quark
{-# LINE 278 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
instance GErrorClass FileChooserError where
  gerrorDomain _ = fileChooserErrorDomain
fileChooserSetAction :: FileChooserClass self => self
 -> FileChooserAction 
                      
 -> IO ()
fileChooserSetAction self action =
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_action argPtr1 arg2)
{-# LINE 293 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    ((fromIntegral . fromEnum) action)
fileChooserGetAction :: FileChooserClass self => self -> IO FileChooserAction
fileChooserGetAction self =
  liftM (toEnum . fromIntegral) $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_action argPtr1)
{-# LINE 303 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserSetLocalOnly :: FileChooserClass self => self -> Bool -> IO ()
fileChooserSetLocalOnly self localOnly =
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_local_only argPtr1 arg2)
{-# LINE 315 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (fromBool localOnly)
fileChooserGetLocalOnly :: FileChooserClass self => self -> IO Bool
fileChooserGetLocalOnly self =
  liftM toBool $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_local_only argPtr1)
{-# LINE 325 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserSetSelectMultiple :: FileChooserClass self => self -> Bool -> IO ()
fileChooserSetSelectMultiple self selectMultiple =
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_select_multiple argPtr1 arg2)
{-# LINE 334 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (fromBool selectMultiple)
fileChooserGetSelectMultiple :: FileChooserClass self => self -> IO Bool
fileChooserGetSelectMultiple self =
  liftM toBool $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_select_multiple argPtr1)
{-# LINE 344 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserSetCurrentName :: (FileChooserClass self, GlibFilePath fp) => self
 -> fp 
 -> IO ()
fileChooserSetCurrentName self name =
  withUTFFilePath name $ \namePtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_current_name argPtr1 arg2)
{-# LINE 362 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    namePtr
fileChooserGetFilename :: (FileChooserClass self, GlibFilePath fp) => self
 -> IO (Maybe fp) 
                        
                        
fileChooserGetFilename self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_filename argPtr1)
{-# LINE 381 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= maybePeek peekUTFFilePath
fileChooserSetFilename :: FileChooserClass self => self
 -> FilePath 
 -> IO Bool 
             
fileChooserSetFilename self filename =
  liftM toBool $
  withCString filename $ \filenamePtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_filename argPtr1 arg2)
{-# LINE 423 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    filenamePtr
fileChooserSelectFilename :: FileChooserClass self => self
 -> FilePath 
 -> IO Bool 
             
fileChooserSelectFilename self filename =
  liftM toBool $
  withCString filename $ \filenamePtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_select_filename argPtr1 arg2)
{-# LINE 442 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    filenamePtr
fileChooserUnselectFilename :: FileChooserClass self => self
 -> FilePath 
 -> IO ()
fileChooserUnselectFilename self filename =
  withCString filename $ \filenamePtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_unselect_filename argPtr1 arg2)
{-# LINE 459 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    filenamePtr
fileChooserSelectAll :: FileChooserClass self => self -> IO ()
fileChooserSelectAll self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_select_all argPtr1)
{-# LINE 468 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserUnselectAll :: FileChooserClass self => self -> IO ()
fileChooserUnselectAll self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_unselect_all argPtr1)
{-# LINE 475 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserGetFilenames :: FileChooserClass self => self -> IO [FilePath]
fileChooserGetFilenames self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_filenames argPtr1)
{-# LINE 488 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= fromStringGSList
fileChooserSetCurrentFolder :: FileChooserClass self => self
 -> FilePath 
 -> IO Bool 
             
fileChooserSetCurrentFolder self filename =
  liftM toBool $
  withCString filename $ \filenamePtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_current_folder argPtr1 arg2)
{-# LINE 507 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    filenamePtr
fileChooserGetCurrentFolder :: FileChooserClass self => self
 -> IO (Maybe FilePath) 
                        
                        
fileChooserGetCurrentFolder self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_current_folder argPtr1)
{-# LINE 523 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= maybePeek readCString
fileChooserGetURI :: FileChooserClass self => self
 -> IO (Maybe String) 
                      
fileChooserGetURI self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_uri argPtr1)
{-# LINE 539 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= maybePeek readCString
fileChooserSetURI :: FileChooserClass self => self
 -> String 
 -> IO Bool 
            
fileChooserSetURI self uri =
  liftM toBool $
  withCString uri $ \uriPtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_uri argPtr1 arg2)
{-# LINE 575 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    uriPtr
fileChooserSelectURI :: FileChooserClass self => self
 -> String 
 -> IO Bool 
            
fileChooserSelectURI self uri =
  liftM toBool $
  withCString uri $ \uriPtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_select_uri argPtr1 arg2)
{-# LINE 590 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    uriPtr
fileChooserUnselectURI :: FileChooserClass self => self
 -> String 
 -> IO ()
fileChooserUnselectURI self uri =
  withCString uri $ \uriPtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_unselect_uri argPtr1 arg2)
{-# LINE 603 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    uriPtr
fileChooserGetURIs :: FileChooserClass self => self -> IO [String]
fileChooserGetURIs self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_uris argPtr1)
{-# LINE 612 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= fromStringGSList
fileChooserSetCurrentFolderURI :: FileChooserClass self => self
 -> String 
 -> IO Bool 
            
fileChooserSetCurrentFolderURI self uri =
  liftM toBool $
  withCString uri $ \uriPtr ->
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_current_folder_uri argPtr1 arg2)
{-# LINE 627 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    uriPtr
fileChooserGetCurrentFolderURI :: FileChooserClass self => self
 -> IO String 
fileChooserGetCurrentFolderURI self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_current_folder_uri argPtr1)
{-# LINE 637 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= readCString
fileChooserSetPreviewWidget :: (FileChooserClass self, WidgetClass previewWidget) => self
 -> previewWidget 
 -> IO ()
fileChooserSetPreviewWidget self previewWidget =
  (\(FileChooser arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_file_chooser_set_preview_widget argPtr1 argPtr2)
{-# LINE 658 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (toWidget previewWidget)
fileChooserGetPreviewWidget :: FileChooserClass self => self
 -> IO (Maybe Widget) 
fileChooserGetPreviewWidget self =
  maybeNull (makeNewObject mkWidget) $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_preview_widget argPtr1)
{-# LINE 668 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserSetPreviewWidgetActive :: FileChooserClass self => self
 -> Bool 
 -> IO ()
fileChooserSetPreviewWidgetActive self active =
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_preview_widget_active argPtr1 arg2)
{-# LINE 681 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (fromBool active)
fileChooserGetPreviewWidgetActive :: FileChooserClass self => self
 -> IO Bool 
            
fileChooserGetPreviewWidgetActive self =
  liftM toBool $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_preview_widget_active argPtr1)
{-# LINE 694 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserSetUsePreviewLabel :: FileChooserClass self => self
 -> Bool 
          
 -> IO ()
fileChooserSetUsePreviewLabel self useLabel =
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_use_preview_label argPtr1 arg2)
{-# LINE 709 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (fromBool useLabel)
fileChooserGetUsePreviewLabel :: FileChooserClass self => self
 -> IO Bool 
            
fileChooserGetUsePreviewLabel self =
  liftM toBool $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_use_preview_label argPtr1)
{-# LINE 721 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserGetPreviewFilename :: FileChooserClass self => self
 -> IO (Maybe FilePath) 
                        
                        
fileChooserGetPreviewFilename self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_preview_filename argPtr1)
{-# LINE 735 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= maybePeek readCString
fileChooserGetPreviewURI :: FileChooserClass self => self
 -> IO (Maybe String) 
                      
fileChooserGetPreviewURI self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_preview_uri argPtr1)
{-# LINE 747 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= maybePeek readCString
fileChooserSetExtraWidget :: (FileChooserClass self, WidgetClass extraWidget) => self
 -> extraWidget 
 -> IO ()
fileChooserSetExtraWidget self extraWidget =
  (\(FileChooser arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_file_chooser_set_extra_widget argPtr1 argPtr2)
{-# LINE 757 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (toWidget extraWidget)
fileChooserGetExtraWidget :: FileChooserClass self => self
 -> IO (Maybe Widget) 
fileChooserGetExtraWidget self =
  maybeNull (makeNewObject mkWidget) $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_extra_widget argPtr1)
{-# LINE 767 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserAddFilter :: FileChooserClass self => self -> FileFilter -> IO ()
fileChooserAddFilter self filter =
  (\(FileChooser arg1) (FileFilter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_file_chooser_add_filter argPtr1 argPtr2)
{-# LINE 776 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    filter
fileChooserRemoveFilter :: FileChooserClass self => self -> FileFilter -> IO ()
fileChooserRemoveFilter self filter =
  (\(FileChooser arg1) (FileFilter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_file_chooser_remove_filter argPtr1 argPtr2)
{-# LINE 785 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    filter
fileChooserListFilters :: FileChooserClass self => self -> IO [FileFilter]
fileChooserListFilters self = do
  filterList <- (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_list_filters argPtr1)
{-# LINE 794 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  filterPtrs <- fromGSList filterList
  mapM (makeNewObject mkFileFilter . return) filterPtrs
fileChooserSetFilter :: FileChooserClass self => self -> FileFilter -> IO ()
fileChooserSetFilter self filter =
  (\(FileChooser arg1) (FileFilter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_file_chooser_set_filter argPtr1 argPtr2)
{-# LINE 807 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    filter
fileChooserGetFilter :: FileChooserClass self => self
 -> IO (Maybe FileFilter) 
fileChooserGetFilter self =
  maybeNull (makeNewObject mkFileFilter) $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_filter argPtr1)
{-# LINE 817 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserAddShortcutFolder :: FileChooserClass self => self
 -> FilePath 
 -> IO ()
fileChooserAddShortcutFolder self folder =
  propagateGError $ \errorPtr ->
  withCString folder $ \folderPtr -> do
  (\(FileChooser arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_add_shortcut_folder argPtr1 arg2 arg3)
{-# LINE 836 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    folderPtr
    errorPtr
  return ()
fileChooserRemoveShortcutFolder :: FileChooserClass self => self
 -> FilePath 
 -> IO ()
fileChooserRemoveShortcutFolder self folder =
  propagateGError $ \errorPtr ->
  withCString folder $ \folderPtr -> do
  (\(FileChooser arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_remove_shortcut_folder argPtr1 arg2 arg3)
{-# LINE 856 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    folderPtr
    errorPtr
  return ()
fileChooserListShortcutFolders :: FileChooserClass self => self -> IO [String]
fileChooserListShortcutFolders self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_list_shortcut_folders argPtr1)
{-# LINE 871 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= fromStringGSList
fileChooserAddShortcutFolderURI :: FileChooserClass self => self
 -> String 
 -> IO ()
fileChooserAddShortcutFolderURI self uri =
  propagateGError $ \errorPtr ->
  withCString uri $ \uriPtr -> do
  (\(FileChooser arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_add_shortcut_folder_uri argPtr1 arg2 arg3)
{-# LINE 889 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    uriPtr
    errorPtr
  return ()
fileChooserRemoveShortcutFolderURI :: FileChooserClass self => self
 -> String 
 -> IO ()
fileChooserRemoveShortcutFolderURI self uri =
  propagateGError $ \errorPtr ->
  withCString uri $ \uriPtr -> do
  (\(FileChooser arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_remove_shortcut_folder_uri argPtr1 arg2 arg3)
{-# LINE 903 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    uriPtr
    errorPtr
  return ()
fileChooserListShortcutFolderURIs :: FileChooserClass self => self -> IO [String]
fileChooserListShortcutFolderURIs self =
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_list_shortcut_folder_uris argPtr1)
{-# LINE 914 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
  >>= fromStringGSList
fileChooserSetShowHidden :: FileChooserClass self => self
 -> Bool 
          
 -> IO ()
fileChooserSetShowHidden self showHidden =
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_show_hidden argPtr1 arg2)
{-# LINE 928 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (fromBool showHidden)
fileChooserGetShowHidden :: FileChooserClass self => self
 -> IO Bool 
fileChooserGetShowHidden self =
  liftM toBool $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_show_hidden argPtr1)
{-# LINE 941 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserSetDoOverwriteConfirmation :: FileChooserClass self => self
 -> Bool 
          
 -> IO ()
fileChooserSetDoOverwriteConfirmation self doOverwriteConfirmation =
  (\(FileChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_set_do_overwrite_confirmation argPtr1 arg2)
{-# LINE 965 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
    (fromBool doOverwriteConfirmation)
fileChooserGetDoOverwriteConfirmation :: FileChooserClass self => self
 -> IO Bool 
            
fileChooserGetDoOverwriteConfirmation self =
  liftM toBool $
  (\(FileChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_get_do_overwrite_confirmation argPtr1)
{-# LINE 979 "./Graphics/UI/Gtk/Selectors/FileChooser.chs" #-}
    (toFileChooser self)
fileChooserUsePreviewLabel :: FileChooserClass self => Attr self Bool
fileChooserUsePreviewLabel = newAttr
  fileChooserGetUsePreviewLabel
  fileChooserSetUsePreviewLabel
fileChooserShowHidden :: FileChooserClass self => Attr self Bool
fileChooserShowHidden = newAttr
  fileChooserGetShowHidden
  fileChooserSetShowHidden
fileChooserSelectMultiple :: FileChooserClass self => Attr self Bool
fileChooserSelectMultiple = newAttr
  fileChooserGetSelectMultiple
  fileChooserSetSelectMultiple
fileChooserPreviewWidgetActive :: FileChooserClass self => Attr self Bool
fileChooserPreviewWidgetActive = newAttr
  fileChooserGetPreviewWidgetActive
  fileChooserSetPreviewWidgetActive
fileChooserPreviewWidget :: (FileChooserClass self, WidgetClass previewWidget) => ReadWriteAttr self (Maybe Widget) previewWidget
fileChooserPreviewWidget = newAttr
  fileChooserGetPreviewWidget
  fileChooserSetPreviewWidget
fileChooserLocalOnly :: FileChooserClass self => Attr self Bool
fileChooserLocalOnly = newAttr
  fileChooserGetLocalOnly
  fileChooserSetLocalOnly
fileChooserFilter :: FileChooserClass self => ReadWriteAttr self (Maybe FileFilter) FileFilter
fileChooserFilter = newAttr
  fileChooserGetFilter
  fileChooserSetFilter
fileChooserExtraWidget :: (FileChooserClass self, WidgetClass extraWidget) => ReadWriteAttr self (Maybe Widget) extraWidget
fileChooserExtraWidget = newAttr
  fileChooserGetExtraWidget
  fileChooserSetExtraWidget
fileChooserDoOverwriteConfirmation :: FileChooserClass self => Attr self Bool
fileChooserDoOverwriteConfirmation = newAttr
  fileChooserGetDoOverwriteConfirmation
  fileChooserSetDoOverwriteConfirmation
fileChooserAction :: FileChooserClass self => Attr self FileChooserAction
fileChooserAction = newAttr
  fileChooserGetAction
  fileChooserSetAction
currentFolderChanged :: FileChooserClass self => Signal self (IO ())
currentFolderChanged = Signal (connect_NONE__NONE "current-folder-changed")
fileSelectionChanged :: FileChooserClass self => Signal self (IO ())
fileSelectionChanged = Signal (connect_NONE__NONE "selection-changed")
updatePreview :: FileChooserClass self => Signal self (IO ())
updatePreview = Signal (connect_NONE__NONE "update-preview")
fileActivated :: FileChooserClass self => Signal self (IO ())
fileActivated = Signal (connect_NONE__NONE "file-activated")
confirmOverwrite :: FileChooserClass self => Signal self (IO FileChooserConfirmation)
confirmOverwrite = Signal (connect_NONE__ENUM "confirm-overwrite")
onCurrentFolderChanged, afterCurrentFolderChanged :: FileChooserClass self => self
 -> IO ()
 -> IO (ConnectId self)
onCurrentFolderChanged = connect_NONE__NONE "current-folder-changed" False
afterCurrentFolderChanged = connect_NONE__NONE "current-folder-changed" True
{-# DEPRECATED onCurrentFolderChanged "use currentFolderChanged instead" #-}
{-# DEPRECATED afterCurrentFolderChanged "use currentFolderChanged instead" #-}
onUpdatePreview, afterUpdatePreview :: FileChooserClass self => self
 -> IO ()
 -> IO (ConnectId self)
onUpdatePreview = connect_NONE__NONE "update-preview" False
afterUpdatePreview = connect_NONE__NONE "update-preview" True
{-# DEPRECATED onUpdatePreview "use updatePreview instead" #-}
{-# DEPRECATED afterUpdatePreview "use updatePreview instead" #-}
onFileActivated, afterFileActivated :: FileChooserClass self => self
 -> IO ()
 -> IO (ConnectId self)
onFileActivated = connect_NONE__NONE "file-activated" False
afterFileActivated = connect_NONE__NONE "file-activated" True
{-# DEPRECATED onFileActivated "use fileActivated instead" #-}
{-# DEPRECATED afterFileActivated "use fileActivated instead" #-}
onConfirmOverwrite, afterConfirmOverwrite :: FileChooserClass self => self
 -> IO FileChooserConfirmation
 -> IO (ConnectId self)
onConfirmOverwrite = connect_NONE__ENUM "confirm-overwrite" False
afterConfirmOverwrite = connect_NONE__ENUM "confirm-overwrite" True
{-# DEPRECATED onConfirmOverwrite "use confirmOverwrite instead" #-}
{-# DEPRECATED afterConfirmOverwrite "use confirmOverwrite instead" #-}
fromStringGSList :: GSList -> IO [String]
fromStringGSList strList = do
  strPtrs <- fromGSList strList
  mapM readCString strPtrs
foreign import ccall unsafe "gtk_file_chooser_error_quark"
  gtk_file_chooser_error_quark :: (IO CUInt)
foreign import ccall safe "gtk_file_chooser_set_action"
  gtk_file_chooser_set_action :: ((Ptr FileChooser) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_action"
  gtk_file_chooser_get_action :: ((Ptr FileChooser) -> (IO CInt))
foreign import ccall safe "gtk_file_chooser_set_local_only"
  gtk_file_chooser_set_local_only :: ((Ptr FileChooser) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_local_only"
  gtk_file_chooser_get_local_only :: ((Ptr FileChooser) -> (IO CInt))
foreign import ccall safe "gtk_file_chooser_set_select_multiple"
  gtk_file_chooser_set_select_multiple :: ((Ptr FileChooser) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_select_multiple"
  gtk_file_chooser_get_select_multiple :: ((Ptr FileChooser) -> (IO CInt))
foreign import ccall safe "gtk_file_chooser_set_current_name"
  gtk_file_chooser_set_current_name :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_filename"
  gtk_file_chooser_get_filename :: ((Ptr FileChooser) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_file_chooser_set_filename"
  gtk_file_chooser_set_filename :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_file_chooser_select_filename"
  gtk_file_chooser_select_filename :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_file_chooser_unselect_filename"
  gtk_file_chooser_unselect_filename :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_select_all"
  gtk_file_chooser_select_all :: ((Ptr FileChooser) -> (IO ()))
foreign import ccall safe "gtk_file_chooser_unselect_all"
  gtk_file_chooser_unselect_all :: ((Ptr FileChooser) -> (IO ()))
foreign import ccall safe "gtk_file_chooser_get_filenames"
  gtk_file_chooser_get_filenames :: ((Ptr FileChooser) -> (IO (Ptr ())))
foreign import ccall safe "gtk_file_chooser_set_current_folder"
  gtk_file_chooser_set_current_folder :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_file_chooser_get_current_folder"
  gtk_file_chooser_get_current_folder :: ((Ptr FileChooser) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_file_chooser_get_uri"
  gtk_file_chooser_get_uri :: ((Ptr FileChooser) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_file_chooser_set_uri"
  gtk_file_chooser_set_uri :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_file_chooser_select_uri"
  gtk_file_chooser_select_uri :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_file_chooser_unselect_uri"
  gtk_file_chooser_unselect_uri :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_uris"
  gtk_file_chooser_get_uris :: ((Ptr FileChooser) -> (IO (Ptr ())))
foreign import ccall safe "gtk_file_chooser_set_current_folder_uri"
  gtk_file_chooser_set_current_folder_uri :: ((Ptr FileChooser) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_file_chooser_get_current_folder_uri"
  gtk_file_chooser_get_current_folder_uri :: ((Ptr FileChooser) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_file_chooser_set_preview_widget"
  gtk_file_chooser_set_preview_widget :: ((Ptr FileChooser) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_preview_widget"
  gtk_file_chooser_get_preview_widget :: ((Ptr FileChooser) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_file_chooser_set_preview_widget_active"
  gtk_file_chooser_set_preview_widget_active :: ((Ptr FileChooser) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_preview_widget_active"
  gtk_file_chooser_get_preview_widget_active :: ((Ptr FileChooser) -> (IO CInt))
foreign import ccall safe "gtk_file_chooser_set_use_preview_label"
  gtk_file_chooser_set_use_preview_label :: ((Ptr FileChooser) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_use_preview_label"
  gtk_file_chooser_get_use_preview_label :: ((Ptr FileChooser) -> (IO CInt))
foreign import ccall safe "gtk_file_chooser_get_preview_filename"
  gtk_file_chooser_get_preview_filename :: ((Ptr FileChooser) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_file_chooser_get_preview_uri"
  gtk_file_chooser_get_preview_uri :: ((Ptr FileChooser) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_file_chooser_set_extra_widget"
  gtk_file_chooser_set_extra_widget :: ((Ptr FileChooser) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_extra_widget"
  gtk_file_chooser_get_extra_widget :: ((Ptr FileChooser) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_file_chooser_add_filter"
  gtk_file_chooser_add_filter :: ((Ptr FileChooser) -> ((Ptr FileFilter) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_remove_filter"
  gtk_file_chooser_remove_filter :: ((Ptr FileChooser) -> ((Ptr FileFilter) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_list_filters"
  gtk_file_chooser_list_filters :: ((Ptr FileChooser) -> (IO (Ptr ())))
foreign import ccall safe "gtk_file_chooser_set_filter"
  gtk_file_chooser_set_filter :: ((Ptr FileChooser) -> ((Ptr FileFilter) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_filter"
  gtk_file_chooser_get_filter :: ((Ptr FileChooser) -> (IO (Ptr FileFilter)))
foreign import ccall safe "gtk_file_chooser_add_shortcut_folder"
  gtk_file_chooser_add_shortcut_folder :: ((Ptr FileChooser) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "gtk_file_chooser_remove_shortcut_folder"
  gtk_file_chooser_remove_shortcut_folder :: ((Ptr FileChooser) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "gtk_file_chooser_list_shortcut_folders"
  gtk_file_chooser_list_shortcut_folders :: ((Ptr FileChooser) -> (IO (Ptr ())))
foreign import ccall safe "gtk_file_chooser_add_shortcut_folder_uri"
  gtk_file_chooser_add_shortcut_folder_uri :: ((Ptr FileChooser) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "gtk_file_chooser_remove_shortcut_folder_uri"
  gtk_file_chooser_remove_shortcut_folder_uri :: ((Ptr FileChooser) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "gtk_file_chooser_list_shortcut_folder_uris"
  gtk_file_chooser_list_shortcut_folder_uris :: ((Ptr FileChooser) -> (IO (Ptr ())))
foreign import ccall safe "gtk_file_chooser_set_show_hidden"
  gtk_file_chooser_set_show_hidden :: ((Ptr FileChooser) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_show_hidden"
  gtk_file_chooser_get_show_hidden :: ((Ptr FileChooser) -> (IO CInt))
foreign import ccall safe "gtk_file_chooser_set_do_overwrite_confirmation"
  gtk_file_chooser_set_do_overwrite_confirmation :: ((Ptr FileChooser) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_file_chooser_get_do_overwrite_confirmation"
  gtk_file_chooser_get_do_overwrite_confirmation :: ((Ptr FileChooser) -> (IO CInt))