views:

530

answers:

2

Hi, I'm trying to get the location of Window's Local AppData folder in a version-agnostic manner using Haskell, and I'm having a bit of trouble doing so. I've tried using the System.Win32.Registry library, and I was able to get the code below (after some trial and error), but I wasn't able to figure out how to use the regQueryValueEx or any other function to get the value I need.

import System.Win32.Types
import System.Win32.Registry

userShellFolders :: IO HKEY
userShellFolders = regOpenKeyEx hKEY_CURRENT_USER "Software\\Microsoft\\Windows\\CurrentVersion\\Explorer\\User Shell Folders\\" kEY_QUERY_VALUE

I also tried looking at the source code for the getAppUserDataDirectory function in the System.Directory module, but that didn't help me either.

Maybe there's an easier way to do this that I'm just missing.

A: 

To read the values from the registry in a useful format quite some code is necessary to convert between Haskell and C types. And that the values in question are usually of type REG_EXPAND_SZ also doesn't help. So it's not pretty, but this works for me:

{-# LANGUAGE ForeignFunctionInterface #-}

import System.Win32.Types
import System.Win32.Registry
import Foreign.Ptr (castPtr)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.C.String (peekCWString, withCWString)
import Control.Exception (bracket, throwIO)

-- // parse a string from a registry value of certain type
parseRegString :: RegValueType -> LPBYTE -> IO String
parseRegString ty mem
   | ty == rEG_SZ        = peekCWString (castPtr mem)
   | ty == rEG_EXPAND_SZ = peekCWString (castPtr mem) >>=
                              expandEnvironmentStrings
   | otherwise           = ioError (userError "Invalid registry value type")

-- // FFI import of the ExpandEnvironmentStrings function needed
-- // to make use of the registry values
expandEnvironmentStrings :: String -> IO String
expandEnvironmentStrings toexpand =
   withCWString toexpand $ \input ->
   allocaBytes 512 $ \output ->
   do c_ExpandEnvironmentStrings input output 256
      peekCWString output
foreign import stdcall unsafe "windows.h ExpandEnvironmentStringsW"
  c_ExpandEnvironmentStrings :: LPCTSTR -> LPTSTR -> DWORD -> IO DWORD

-- // open the registry key
userShellFolders :: IO HKEY
userShellFolders = regOpenKeyEx hKEY_CURRENT_USER
   "Software\\Microsoft\\Windows\\CurrentVersion\\Explorer\\User Shell Folders"
   kEY_QUERY_VALUE

-- // read the actual value
localAppData :: IO String
localAppData =
   bracket userShellFolders regCloseKey $ \usfkey ->
   allocaBytes 512 $ \mem ->
   do ty <- regQueryValueEx usfkey "Local AppData" mem 512
      parseRegString ty mem

main = localAppData >>= print

I'm not sure if all the error cases are handled correctly (like if the passed buffer was to small), so you might want to check the windows docs to see what happens in these cases.

sth
Thank you very much, this does exactly what I need.
Alasdair
Not the documented way to do this, and unclear on which Windows it does work. It may be the closest to what Alasdairn had already, but the API solution is better.
MSalters
I did just go by what Alasdair already had and didn't look for any other Api calls. Anyway, I won't delete this since it might be useful for other people that are trying to read different registry values that don't have a separate Api to access.
sth
Fair point on the 'other registry values' bit. There are certainly some registry keys documented.
MSalters
The reason I tried getting the path from the registry was because the documentation for the app I'm interoperating with says that the registry is how you do should this, luckily it's in wiki format so I was able to correct it.
Alasdair
+6  A: 

If you want portability, you shouldn't access registry directly. There is an API function to get special folders: SHGetFolderPath. You can call it thus:

{-# LANGUAGE ForeignFunctionInterface #-}
import System.Win32.Types
import Graphics.Win32.GDI.Types
import Foreign.C.String
import Foreign.Marshal.Array

foreign import stdcall unsafe "SHGetFolderPathW"
    cSHGetFolderPathW :: HWND -> INT -> HANDLE -> DWORD -> CWString -> IO LONG

maxPath = 260
cSIDL_LOCAL_APPDATA = 0x001c -- //see file ShlObj.h in MS Platform SDK for other CSIDL constants

getShellFolder :: INT -> IO String
getShellFolder csidl = allocaArray0 maxPath $ \path -> do
    cSHGetFolderPathW nullHANDLE csidl nullHANDLE 0 path
    peekCWString path

main = getShellFolder cSIDL_LOCAL_APPDATA >>= putStrLn
robson3.14