-- | Minimal cubemap support (at the moment just some help with the layout)

{-# LANGUAGE CPP #-}
module Data.Bitmap.OpenGL.CubeMap 
  ( 
    CubeMapFace(..)
  )
  where

--------------------------------------------------------------------------------

import Data.Bitmap.IO
import Data.Bitmap.OpenGL

import Graphics.Rendering.OpenGL

--------------------------------------------------------------------------------

-- | The layout:
--
-- >        +------+
-- >        |      |
-- >        | top  |
-- >        |      |
-- > +------+------+------+------+ 
-- > |      |      |      |      |
-- > | left |front |right | back |
-- > |      |      |      |      |
-- > +------+------+------+------+ 
-- >        |      |
-- >        |bottom|      
-- >        |      |
-- >        +------+
--
data CubeMapFace
  = CubeFront
  | CubeBack
  | CubeTop
  | CubeDown
  | CubeLeft
  | CubeRight
  deriving (Eq,Ord,Show)
 
#if OPENGL_VERSION >= 29
target :: CubeMapFace -> TextureTargetCubeMapFace 
#else
target :: CubeMapFace -> CubeMapTarget 
#endif   
target face = case face of
  CubeRight -> TextureCubeMapPositiveX
  CubeLeft  -> TextureCubeMapNegativeX
  CubeTop   -> TextureCubeMapPositiveY 
  CubeDown  -> TextureCubeMapNegativeY
  CubeFront -> TextureCubeMapPositiveZ
  CubeBack  -> TextureCubeMapNegativeZ  
  
--------------------------------------------------------------------------------