module System.GIO.File.ContentType (
    contentTypeEquals,
    contentTypeIsA,
    contentTypeIsUnknown,
    contentTypeGetDescription,
    contentTypeGetMimeType,
    contentTypeGetIcon,
    contentTypeCanBeExecutable,
    contentTypeFromMimeType,
    contentTypeGuess,
    contentTypeGuessForTree,
    contentTypesGetRegistered,
    ) where
import Control.Monad
import System.GIO.Enums
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GError
import System.Glib.GList
import System.Glib.GObject
import System.Glib.UTFString
import System.GIO.Types
contentTypeEquals ::
    GlibString string
 => string
 -> string
 -> Bool 
contentTypeEquals type1 type2 =
  toBool $ unsafePerformIO $
  withUTFString type1 $ \ type1Ptr ->
  withUTFString type2 $ \ type2Ptr ->
  g_content_type_equals type1Ptr type2Ptr
contentTypeIsA ::
    GlibString string
 => string
 -> string
 -> Bool 
contentTypeIsA type1 supertype =
  toBool $ unsafePerformIO $
  withUTFString type1 $ \ type1Ptr ->
  withUTFString supertype $ \ supertypePtr ->
  g_content_type_equals type1Ptr supertypePtr
contentTypeIsUnknown ::
    GlibString string
 => string
 -> Bool 
contentTypeIsUnknown typ =
  toBool $ unsafePerformIO $
  withUTFString typ $ \ typPtr ->
  g_content_type_is_unknown typPtr
contentTypeGetDescription ::
    GlibString string
 => string
 -> string 
contentTypeGetDescription typ =
  unsafePerformIO $
  withUTFString typ $ \ typPtr ->
  g_content_type_get_description typPtr
  >>= readUTFString
contentTypeGetMimeType ::
    GlibString string
 => string
 -> string 
contentTypeGetMimeType typ =
  unsafePerformIO $
  withUTFString typ $ \ typPtr ->
  g_content_type_get_mime_type typPtr
  >>= readUTFString
contentTypeGetIcon ::
    GlibString string
 => string
 -> Icon 
contentTypeGetIcon typ =
  unsafePerformIO $ wrapNewGObject mkIcon $
  withUTFString typ $ \ typPtr ->
  g_content_type_get_icon typPtr
contentTypeCanBeExecutable ::
    GlibString string
 => string
 -> Bool 
contentTypeCanBeExecutable typ =
  toBool $ unsafePerformIO $
  withUTFString typ $ \ typPtr ->
  g_content_type_can_be_executable typPtr
contentTypeFromMimeType ::
    GlibString string
 => string 
 -> string
contentTypeFromMimeType mimeType =
  unsafePerformIO $
  withUTFString mimeType $ \ mimeTypePtr ->
  g_content_type_from_mime_type mimeTypePtr
  >>= readUTFString
contentTypeGuess ::
    (GlibFilePath fp, GlibString string)
 => fp
 -> string 
 -> Int 
 -> IO (Bool, string) 
contentTypeGuess filename dat dataSize =
  withUTFFilePath filename $ \ filenamePtr ->
  withUTFString dat $ \ datPtr ->
  alloca $ \ resultUncertainPtr -> do
  strPtr <- g_content_type_guess
           filenamePtr
           (castPtr datPtr)
           (fromIntegral dataSize)
           (castPtr resultUncertainPtr)
  resultUncertain <- peek resultUncertainPtr
  str <- readUTFString strPtr
  return (resultUncertain, str)
contentTypeGuessForTree ::
    (FileClass file, GlibString string)
 => file 
 -> IO [string] 
contentTypeGuessForTree root =
  (\(File arg1) -> withForeignPtr arg1 $ \argPtr1 ->g_content_type_guess_for_tree argPtr1) (toFile root)
  >>= readUTFStringArray0
contentTypesGetRegistered ::
    GlibString string
 => IO [string] 
contentTypesGetRegistered = do
  glistPtr <- g_content_types_get_registered
  strPtrs <- fromGList glistPtr
  mapM readUTFString strPtrs
foreign import ccall safe "g_content_type_equals"
  g_content_type_equals :: ((Ptr CChar) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "g_content_type_is_unknown"
  g_content_type_is_unknown :: ((Ptr CChar) -> (IO CInt))
foreign import ccall safe "g_content_type_get_description"
  g_content_type_get_description :: ((Ptr CChar) -> (IO (Ptr CChar)))
foreign import ccall safe "g_content_type_get_mime_type"
  g_content_type_get_mime_type :: ((Ptr CChar) -> (IO (Ptr CChar)))
foreign import ccall safe "g_content_type_get_icon"
  g_content_type_get_icon :: ((Ptr CChar) -> (IO (Ptr Icon)))
foreign import ccall safe "g_content_type_can_be_executable"
  g_content_type_can_be_executable :: ((Ptr CChar) -> (IO CInt))
foreign import ccall safe "g_content_type_from_mime_type"
  g_content_type_from_mime_type :: ((Ptr CChar) -> (IO (Ptr CChar)))
foreign import ccall safe "g_content_type_guess"
  g_content_type_guess :: ((Ptr CChar) -> ((Ptr CUChar) -> (CULong -> ((Ptr CInt) -> (IO (Ptr CChar))))))
foreign import ccall safe "g_content_type_guess_for_tree"
  g_content_type_guess_for_tree :: ((Ptr File) -> (IO (Ptr (Ptr CChar))))
foreign import ccall safe "g_content_types_get_registered"
  g_content_types_get_registered :: (IO (Ptr ()))