-- GENERATED by C->Haskell Compiler, version 0.16.3 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TypeSynonymInstances #-}

-- This source file is part of HGamer3D
-- (A project to enable 3D game development in Haskell)
-- For the latest info, see http://www.althainz.de/HGamer3D.html
-- 

-- (c) 2011, 2012 Peter Althainz
-- 
-- Licensed under the Apache License, Version 2.0 (the "License");
-- you may not use this file except in compliance with the License.
-- You may obtain a copy of the License at
-- 
--     http://www.apache.org/licenses/LICENSE-2.0
-- 
-- Unless required by applicable law or agreed to in writing, software
-- distributed under the License is distributed on an "AS IS" BASIS,
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-- See the License for the specific language governing permissions and
-- limitations under the License.
-- 


-- ClassResourceGroupManager.chs

-- 

module HGamer3D.Bindings.Ogre.ClassResourceGroupManager where

import Foreign
import Foreign.Ptr
import Foreign.C

import HGamer3D.Data.HG3DClass
import HGamer3D.Data.Vector
import HGamer3D.Data.Colour
import HGamer3D.Data.Angle

import HGamer3D.Bindings.Ogre.Utils
{-# LINE 40 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}
import HGamer3D.Bindings.Ogre.ClassPtr
{-# LINE 41 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}
import HGamer3D.Bindings.Ogre.StructHG3DClass
{-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | 
new :: IO (HG3DClass)
 -- ^ 
new =
  alloca $ \a1' -> 
  new'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | 
delete :: HG3DClass  -- ^ classpointer - pointer of Class instance which is going to be deleted.
  ->  IO ()
 -- ^ 
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
{-# LINE 51 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Create a resource group.
--A resource group allows you to define a set of resources that can be loaded / unloaded as a unit. For example, it might be all the resources used for the level of a game. There is always one predefined resource group called ResourceGroupManager::DEFAULT_RESOURCE_GROUP_NAMEResourceGroupManager::INTERNAL_RESOURCE_GROUP_NAMEResourceGroupManager::AUTODETECT_RESOURCE_GROUP_NAMEOnce you have defined a resource group, resources which will be loaded as part of it are defined in one of 3 ways: 
--
--
--
--
--
--
--
createResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name to give the resource group. 
  ->  Bool  -- ^ inGlobalPool - if true the resource will be loaded even a different group was requested in the load method as a parameter. 
  ->  IO ()
 -- ^ 
createResourceGroup a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = fromBool a3} in 
  createResourceGroup'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 57 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Initialises a resource group.
--After creating a resource group, adding some resource locations, and perhaps pre-declaring some resources using declareResource()
--
--
--
--
--ResourceFailure to call this method means that loadResourceGroup will do nothing, and any resources you define in scripts will not be found. Similarly, once you have called this method you won't be able to pick up any new scripts or pre-declared resources, unless you call clearResourceGroup, set up declared resources, and call this method again. When you call Root::initialiseRoot::initialise
initialiseResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name of the resource group to initialise 
  ->  IO ()
 -- ^ 
initialiseResourceGroup a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  initialiseResourceGroup'_ a1' a2' >>= \res ->
  return ()
{-# LINE 62 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Initialise all resource groups which are yet to be initialised.
--ResourceGroupManager::intialiseResourceGroup 
initialiseAllResourceGroups :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
initialiseAllResourceGroups a1 =
  withHG3DClass a1 $ \a1' -> 
  initialiseAllResourceGroups'_ a1' >>= \res ->
  return ()
{-# LINE 66 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Prepares a resource group.
--Prepares any created resources which are part of the named group. Note that resources must have already been created by calling ResourceManager::createdeclareResource()ResourceGroupManager::linkWorldGeometryToResourceGroup
prepareResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name of the resource group to prepare. 
  ->  Bool  -- ^ prepareMainResources - If true, prepares normal resources associated with the group (you might want to set this to false if you wanted to just prepare world geometry in bulk) 
  ->  Bool  -- ^ prepareWorldGeom - If true, prepares any linked world geometry 
  ->  IO ()
 -- ^ 
prepareResourceGroup a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = fromBool a3} in 
  let {a4' = fromBool a4} in 
  prepareResourceGroup'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 73 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Loads a resource group.
--Loads any created resources which are part of the named group. Note that resources must have already been created by calling ResourceManager::createdeclareResource()ResourceGroupManager::linkWorldGeometryToResourceGroup
loadResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name of the resource group to load. 
  ->  Bool  -- ^ loadMainResources - If true, loads normal resources associated with the group (you might want to set this to false if you wanted to just load world geometry in bulk) 
  ->  Bool  -- ^ loadWorldGeom - If true, loads any linked world geometry 
  ->  IO ()
 -- ^ 
loadResourceGroup a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = fromBool a3} in 
  let {a4' = fromBool a4} in 
  loadResourceGroup'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 80 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Unloads a resource group.
--This method unloads all the resources that have been declared as being part of the named resource group. Note that these resources will still exist in their respective ResourceManagerResource::isReloadable
unloadResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name to of the resource group to unload. 
  ->  Bool  -- ^ reloadableOnly - If set to true, only unload the resource that is reloadable. Because some resources isn't reloadable, they will be unloaded but can't load them later. Thus, you might not want to them unloaded. Or, you might unload all of them, and then populate them manually later. 
  ->  IO ()
 -- ^ 
unloadResourceGroup a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = fromBool a3} in 
  unloadResourceGroup'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 86 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Unload all resources which are not referenced by any other object.
--This method behaves like unloadResourceGroup, except that it only unloads resources in the group which are not in use, ie not referenced by other objects. This allows you to free up some memory selectively whilst still keeping the group around (and the resources present, just not using much memory). 
unloadUnreferencedResourcesInGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name of the group to check for unreferenced resources 
  ->  Bool  -- ^ reloadableOnly - If true (the default), only unloads resources which can be subsequently automatically reloaded 
  ->  IO ()
 -- ^ 
unloadUnreferencedResourcesInGroup a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = fromBool a3} in 
  unloadUnreferencedResourcesInGroup'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 92 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Clears a resource group. 
--This method unloads all resources in the group, but in addition it removes all those resources from their ResourceManagers, and then clears all the members from the list. That means after calling this method, there are no resources declared as part of the named group any more. Resource
clearResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name to of the resource group to clear. 
  ->  IO ()
 -- ^ 
clearResourceGroup a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  clearResourceGroup'_ a1' a2' >>= \res ->
  return ()
{-# LINE 97 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Destroys a resource group, clearing it first, destroying the resources
--which are part of it, and then removing it from
--the list of resource groups. 
--
destroyResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name of the resource group to destroy. 
  ->  IO ()
 -- ^ 
destroyResourceGroup a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  destroyResourceGroup'_ a1' a2' >>= \res ->
  return ()
{-# LINE 102 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Checks the status of a resource group.
--Looks at the state of a resource group. If initialiseResourceGroup has been called for the resource group return true, otherwise return false. 
isResourceGroupInitialised :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name to of the resource group to access. 
  ->  IO (Bool)
 -- ^ 
isResourceGroupInitialised a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  isResourceGroupInitialised'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 108 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Checks the status of a resource group.
--Looks at the state of a resource group. If loadResourceGroup has been called for the resource group return true, otherwise return false. 
isResourceGroupLoaded :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name to of the resource group to access. 
  ->  IO (Bool)
 -- ^ 
isResourceGroupLoaded a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  isResourceGroupLoaded'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 114 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | 
resourceGroupExists :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name
  ->  IO (Bool)
 -- ^ 
resourceGroupExists a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  resourceGroupExists'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 120 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Method to add a resource location to for a given resource group. 
--Resource
addResourceLocation :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name of the resource location; probably a directory, zip file, URL etc. 
  ->  String  -- ^ locType - The codename for the resource type, which must correspond to the Archive factory which is providing the implementation. 
  ->  String  -- ^ resGroup - The name of the resource group for which this location is to apply. ResourceGroupManager::DEFAULT_RESOURCE_GROUP_NAME is the default group which always exists, and can be used for resources which are unlikely to be unloaded until application shutdown. Otherwise it must be the name of a group; if it has not already been created with createResourceGroup then it is created automatically. 
  ->  Bool  -- ^ recursive - Whether subdirectories will be searched for files when using a pattern match (such as *.material), and whether subdirectories will be indexed. This can slow down initial loading of the archive and searches. When opening a resource you still need to use the fully qualified name, this allows duplicate names in alternate paths. 
  ->  IO ()
 -- ^ 
addResourceLocation a1 a2 a3 a4 a5 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  withCString a4 $ \a4' -> 
  let {a5' = fromBool a5} in 
  addResourceLocation'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 128 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Removes a resource location from the search path. 
removeResourceLocation :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name
  ->  String  -- ^ resGroup
  ->  IO ()
 -- ^ 
removeResourceLocation a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  removeResourceLocation'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 134 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Verify if a resource location exists for the given group. 
resourceLocationExists :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name
  ->  String  -- ^ resGroup
  ->  IO (Bool)
 -- ^ 
resourceLocationExists a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  alloca $ \a4' -> 
  resourceLocationExists'_ a1' a2' a3' a4' >>= \res ->
  peekBoolUtil  a4'>>= \a4'' -> 
  return (a4'')
{-# LINE 141 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Undeclare a resource.
--Note that this will not cause it to be unloaded if it is already loaded, nor will it destroy a resource which has already been created if initialiseResourceGroup has been called already. Only unloadResourceGroup / clearResourceGroup / destroyResourceGroup will do that. 
undeclareResource :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name of the resource. 
  ->  String  -- ^ groupName - The name of the group this resource was declared in. 
  ->  IO ()
 -- ^ 
undeclareResource a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  undeclareResource'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 147 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Find out if the named file exists in a group. 
--
resourceExists :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ group - The name of the resource group 
  ->  String  -- ^ filename - Fully qualified name of the file to test for 
  ->  IO (Bool)
 -- ^ 
resourceExists a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  alloca $ \a4' -> 
  resourceExists'_ a1' a2' a3' a4' >>= \res ->
  peekBoolUtil  a4'>>= \a4'' -> 
  return (a4'')
{-# LINE 154 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Find out if the named file exists in any group. 
--
resourceExistsInAnyGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ filename - Fully qualified name of the file to test for 
  ->  IO (Bool)
 -- ^ 
resourceExistsInAnyGroup a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  resourceExistsInAnyGroup'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 160 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Find the group in which a resource exists.
--
findGroupContainingResource :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ filename - Fully qualified name of the file the resource should be found as 
  ->  IO (String)
 -- ^ return value - Name of the resource group the resource was found in. An exception is thrown if the group could not be determined.     
findGroupContainingResource a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloc64k $ \a3' -> 
  findGroupContainingResource'_ a1' a2' a3' >>= \res ->
  peekCString  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 166 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Delete a single resource file.
--
deleteResource :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ filename - The name of the file to delete. 
  ->  String  -- ^ groupName - The name of the group in which to search 
  ->  String  -- ^ locationPattern - If the resource group contains multiple locations, then usually first matching file found in any location will be deleted. If you want to be more specific, you can include a location pattern here and only locations which match that pattern (as determined by StringUtil::match) will be considered candidates for deletion. 
  ->  IO ()
 -- ^ 
deleteResource a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  withCString a4 $ \a4' -> 
  deleteResource'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 173 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Delete all matching resource files.
--
deleteMatchingResources :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ filePattern - The pattern (see StringUtil::match) of the files to delete. 
  ->  String  -- ^ groupName - The name of the group in which to search 
  ->  String  -- ^ locationPattern - If the resource group contains multiple locations, then usually all matching files in any location will be deleted. If you want to be more specific, you can include a location pattern here and only locations which match that pattern (as determined by StringUtil::match) will be considered candidates for deletion. 
  ->  IO ()
 -- ^ 
deleteMatchingResources a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  withCString a4 $ \a4' -> 
  deleteMatchingResources'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 180 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Sets the resource group that 'world' resources will use.
--This is the group which should be used by SceneManagers implementing world geometry when looking for their resources. Defaults to the DEFAULT_RESOURCE_GROUP_NAME but this can be altered. 
setWorldResourceGroupName :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ groupName
  ->  IO ()
 -- ^ 
setWorldResourceGroupName a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  setWorldResourceGroupName'_ a1' a2' >>= \res ->
  return ()
{-# LINE 185 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Gets the resource group that 'world' resources will use. 
getWorldResourceGroupName :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (String)
 -- ^ 
getWorldResourceGroupName a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getWorldResourceGroupName'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 190 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Associates some world geometry with a resource group, causing it to 
--be loaded / unloaded with the resource group.
--You would use this method to essentially defer a call to SceneManager::setWorldGeometry
linkWorldGeometryToResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ group - The name of the resource group 
  ->  String  -- ^ worldGeometry - The parameter which should be passed to setWorldGeometry 
  ->  HG3DClass  -- ^ sceneManager - The SceneManager which should be called 
  ->  IO ()
 -- ^ 
linkWorldGeometryToResourceGroup a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  withHG3DClass a4 $ \a4' -> 
  linkWorldGeometryToResourceGroup'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 197 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Clear any link to world geometry from a resource group.
--Basically undoes a previous call to linkWorldGeometryToResourceGroup. 
unlinkWorldGeometryFromResourceGroup :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ group
  ->  IO ()
 -- ^ 
unlinkWorldGeometryFromResourceGroup a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  unlinkWorldGeometryFromResourceGroup'_ a1' a2' >>= \res ->
  return ()
{-# LINE 202 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- |     Checks the status of a resource group.
--Looks at the state of a resource group. If loadResourceGroup has been called for the resource group return true, otherwise return false. 
isResourceGroupInGlobalPool :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name - The name to of the resource group to access. 
  ->  IO (Bool)
 -- ^ 
isResourceGroupInGlobalPool a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  isResourceGroupInGlobalPool'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 208 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Shutdown all ResourceManagers, performed as part of clean-up. 
shutdownAll :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
shutdownAll a1 =
  withHG3DClass a1 $ \a1' -> 
  shutdownAll'_ a1' >>= \res ->
  return ()
{-# LINE 212 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Override standard Singleton retrieval.
--Why do we do this? Well, it's because the Singleton implementation is in a .h file, which means it gets compiled into anybody who includes it. This is needed for the Singleton template to work, but we actually only want it compiled into the implementation of the class based on the Singleton, not all of them. If we don't change this, we get link errors when trying to use the Singleton-based class from an outside dll. This method just delegates to the template version anyway, but the implementation stays in this single compilation unit, preventing link errors. 
getSingleton :: IO (HG3DClass)
 -- ^ 
getSingleton =
  alloca $ \a1' -> 
  getSingleton'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 216 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}

-- | Override standard Singleton retrieval.
--Why do we do this? Well, it's because the Singleton implementation is in a .h file, which means it gets compiled into anybody who includes it. This is needed for the Singleton template to work, but we actually only want it compiled into the implementation of the class based on the Singleton, not all of them. If we don't change this, we get link errors when trying to use the Singleton-based class from an outside dll. This method just delegates to the template version anyway, but the implementation stays in this single compilation unit, preventing link errors. 
getSingletonPtr :: IO (HG3DClass)
 -- ^ 
getSingletonPtr =
  alloca $ \a1' -> 
  getSingletonPtr'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
{-# LINE 220 ".\\HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs" #-}


foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_construct"
  new'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_createResourceGroup"
  createResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CInt -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_initialiseResourceGroup"
  initialiseResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_initialiseAllResourceGroups"
  initialiseAllResourceGroups'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_prepareResourceGroup"
  prepareResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_loadResourceGroup"
  loadResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CInt -> (CInt -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_unloadResourceGroup"
  unloadResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CInt -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_unloadUnreferencedResourcesInGroup"
  unloadUnreferencedResourcesInGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CInt -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_clearResourceGroup"
  clearResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_destroyResourceGroup"
  destroyResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_isResourceGroupInitialised"
  isResourceGroupInitialised'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_isResourceGroupLoaded"
  isResourceGroupLoaded'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_resourceGroupExists"
  resourceGroupExists'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_addResourceLocation"
  addResourceLocation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (CInt -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_removeResourceLocation"
  removeResourceLocation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_resourceLocationExists"
  resourceLocationExists'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_undeclareResource"
  undeclareResource'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_resourceExists"
  resourceExists'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_resourceExistsInAnyGroup"
  resourceExistsInAnyGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_findGroupContainingResource"
  findGroupContainingResource'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_deleteResource"
  deleteResource'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_deleteMatchingResources"
  deleteMatchingResources'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_setWorldResourceGroupName"
  setWorldResourceGroupName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_getWorldResourceGroupName"
  getWorldResourceGroupName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_linkWorldGeometryToResourceGroup"
  linkWorldGeometryToResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_unlinkWorldGeometryFromResourceGroup"
  unlinkWorldGeometryFromResourceGroup'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_isResourceGroupInGlobalPool"
  isResourceGroupInGlobalPool'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_shutdownAll"
  shutdownAll'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_getSingleton"
  getSingleton'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassResourceGroupManager.chs.h ogre_rgmgr_getSingletonPtr"
  getSingletonPtr'_ :: ((HG3DClassPtr) -> (IO ()))