System.Win32.Registry... Help?

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"

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

Thank you!
I looked over a lot of the api docs, but not the source ones...
The snippit you found showed me exactly what I needed to do.
*Main> k <- regOpenKey hKEY_CURRENT_USER "Software\\7-Zip"
Loading package bytestring-0.9.2.1 ... linking ... done.
Loading package Win32-2.2.2.0 ... linking ... done.
*Main> withTString "A" $ \v -> regSetValueEx k "foo" rEG_SZ v (length "foo" * s
izeOf(undefined :: TCHAR))
Works perfectly, so I can copy binary values too.
Didn't think to look at the helper functions to see how the regular
version is used from them...
Haven't programmed in a while, must be pretty rusty... LOL.
My project is now saved from going .py! :D
.. not anything against python, I'm using django on another project
and it's great,
but haskell comes to mind for this app....
Thanks.
On Sun, Jul 22, 2012 at 4:33 AM, Simon Peter Nicholls
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
wrote: 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Glad I could help. Win32 / FFI examples are indeed thin on the ground.
As it's a null terminated string in that code, you'll need to add 1 to
the length of "A" when calculating the byte count.
Actually, speaking of Win32 examples, I'll drop a general Win32 UI
hint into the mailing list. I quickly arrived at the need to reflect
state in my Win32 app, but I can only see one Japanese guy out there
with an example of what I discovered by rooting around in Haskell
source.
Here is the elusive secret to Win32 UI programming.....
Graphics.Win32.setWindowClosure.
Aye, with that function to hand, your wndProc can have access to your
most current application values, just like regular recursive
functions.
An example:
wndProc fileList hwnd wmsg wParam lParam
... blah ...
setWindowClosure hwnd (wndProc $ FileInfo fileName : fileList)
Here I construct an extra FileInfo from a file name, cons it onto the
fileList which was passed into my wndProc as the first parameter,
partially apply that new list to wndProc, set it as the window
closure, and I'll have it when processing the next message.
On Sun, Jul 22, 2012 at 4:05 PM, Anonymous Void
Thank you!
I looked over a lot of the api docs, but not the source ones...
The snippit you found showed me exactly what I needed to do.
*Main> k <- regOpenKey hKEY_CURRENT_USER "Software\\7-Zip" Loading package bytestring-0.9.2.1 ... linking ... done. Loading package Win32-2.2.2.0 ... linking ... done. *Main> withTString "A" $ \v -> regSetValueEx k "foo" rEG_SZ v (length "foo" * s izeOf(undefined :: TCHAR))
Works perfectly, so I can copy binary values too. Didn't think to look at the helper functions to see how the regular version is used from them... Haven't programmed in a while, must be pretty rusty... LOL.
My project is now saved from going .py! :D .. not anything against python, I'm using django on another project and it's great, but haskell comes to mind for this app....
Thanks.
On Sun, Jul 22, 2012 at 4:33 AM, Simon Peter Nicholls
wrote: 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
wrote: 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Anonymous Void
-
Simon Peter Nicholls