
The Registry module has code that will be helpful, as it includes a
helper function for the common use case of setting String values.
regSetStringValue :: HKEY -> String -> String -> IO ()
regSetStringValue hk key val =
withTString val $ \ v ->
regSetValueEx hk key rEG_SZ v (length val * sizeOf (undefined::TCHAR))
http://www.haskell.org/ghc/docs/7.4.2/html/libraries/Win32-2.2.2.0/src/Syste...
On Sun, Jul 22, 2012 at 7:11 AM, Anonymous Void
Hi,
I'm working on a project that will require me to create and possibly set registry keys. I don't have much experience with programming on Windows either, but I'm having to learn as you don't get many *nix PCs at a computer repair shop, lol.
I found a mailing list post showing how to read registry keys and was able to make a function based off of it, but I have no idea what to put into some of the arguments for regSetValueEx or regCreateKeyEx, so I'm stuck. Also, what's the best way to recursively traverse trees in the registry, are there any functions for it?
Can someone please help me out with this? Thank you.
{-# 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
---- get_key :: HKEY -> String -> String -> IO String get_key cat loc key = bracket op regCloseKey $ \x -> allocaBytes 512 $ \mem -> do ty <- regQueryValueEx x key mem 512 parseRegString ty mem where op = regOpenKeyEx cat loc kEY_QUERY_VALUE
set_key :: HKEY -> String -> String -> IO () set_key cat loc key = regSetValueEx cat loc rEG_SZ??? "LPTSTR? What do I put here?" magic_win32_number_here? where op = regOpenKeyEx cat loc kEY_SET_VALUE
main = get_key hKEY_CURRENT_USER loc key >>= print where loc = "Software\\7-Zip" key = "Test"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe