{-# OPTIONS_GHC -optc-D_WIN32_IE=0x500 #-}
{-# LINE 1 "libraries\\Win32\\System\\Win32\\Shell.hsc" #-}

{-# LINE 2 "libraries\\Win32\\System\\Win32\\Shell.hsc" #-}
{-# LANGUAGE Safe #-}

{-# LINE 6 "libraries\\Win32\\System\\Win32\\Shell.hsc" #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  System.Win32.Shell
-- Copyright   :  (c) The University of Glasgow 2009
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  Esa Ilari Vuokko <ei@vuokko.info>
-- Stability   :  provisional
-- Portability :  portable
--
-- Win32 stuff from shell32.dll
--
-----------------------------------------------------------------------------

module System.Win32.Shell (
  sHGetFolderPath,
  CSIDL,
  cSIDL_PROFILE,
  cSIDL_APPDATA,
  cSIDL_WINDOWS,
  cSIDL_PERSONAL,
  cSIDL_LOCAL_APPDATA,
  cSIDL_DESKTOPDIRECTORY,
  cSIDL_PROGRAM_FILES,
  SHGetFolderPathFlags,
  sHGFP_TYPE_CURRENT,
  sHGFP_TYPE_DEFAULT
 ) where

import System.Win32.Types
import Graphics.Win32.GDI.Types (HWND)

import Foreign
import Foreign.C
import Control.Monad
import System.IO.Error

#include "windows_cconv.h"

-- for SHGetFolderPath stuff




----------------------------------------------------------------
-- SHGetFolderPath
--
-- XXX: this is deprecated in Vista and later
----------------------------------------------------------------

type CSIDL = CInt

cSIDL_PROFILE   :: CSIDL
cSIDL_PROFILE   =  40
cSIDL_APPDATA   :: CSIDL
cSIDL_APPDATA   =  26
cSIDL_WINDOWS   :: CSIDL
cSIDL_WINDOWS   =  36
cSIDL_PERSONAL  :: CSIDL
cSIDL_PERSONAL  =  5
cSIDL_LOCAL_APPDATA  :: CSIDL
cSIDL_LOCAL_APPDATA  =  28
cSIDL_DESKTOPDIRECTORY  :: CSIDL
cSIDL_DESKTOPDIRECTORY  =  16
cSIDL_PROGRAM_FILES  :: CSIDL
cSIDL_PROGRAM_FILES  =  38

{-# LINE 67 "libraries\\Win32\\System\\Win32\\Shell.hsc" #-}
-- XXX there are lots more of these

type SHGetFolderPathFlags = DWORD

sHGFP_TYPE_CURRENT  :: SHGetFolderPathFlags
sHGFP_TYPE_CURRENT  =  0
sHGFP_TYPE_DEFAULT  :: SHGetFolderPathFlags
sHGFP_TYPE_DEFAULT  =  1

{-# LINE 75 "libraries\\Win32\\System\\Win32\\Shell.hsc" #-}

sHGetFolderPath :: HWND -> CSIDL -> HANDLE -> SHGetFolderPathFlags -> IO String
sHGetFolderPath hwnd csidl hdl flags =
  allocaBytes ((260) * ((1))) $ \pstr -> do
{-# LINE 79 "libraries\\Win32\\System\\Win32\\Shell.hsc" #-}
    r <- c_SHGetFolderPath hwnd csidl hdl flags pstr
    when (r < 0) $ raiseUnsupported "sHGetFolderPath"
    peekTString pstr

raiseUnsupported :: String -> IO ()
raiseUnsupported loc =
   ioError (ioeSetErrorString (mkIOError illegalOperationErrorType loc Nothing Nothing) "unsupported operation")

foreign import WINDOWS_CCONV unsafe "SHGetFolderPathW"
  c_SHGetFolderPath :: HWND -> CInt -> HANDLE -> DWORD -> LPTSTR
                    -> IO HRESULT