Copyright | (c) Alastair Reid, 1997-2003 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | Esa Ilari Vuokko <ei@vuokko.info> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
A collection of FFI declarations for accessing the Win32 registry.
Documentation
hKEY_USERS :: HKEY
regCloseKey :: HKEY -> IO ()
c_RegCloseKey :: PKEY -> IO ErrCode
regCreateKey :: HKEY -> String -> IO HKEY
type RegCreateOptions = DWORD
kEY_NOTIFY :: REGSAM
regCreateKeyEx :: HKEY -> String -> String -> RegCreateOptions -> REGSAM -> Maybe LPSECURITY_ATTRIBUTES -> IO (HKEY, Bool)
c_RegCreateKeyEx :: PKEY -> LPCTSTR -> DWORD -> LPCTSTR -> RegCreateOptions -> REGSAM -> LPSECURITY_ATTRIBUTES -> Ptr PKEY -> Ptr DWORD -> IO ErrCode
regDeleteKey :: HKEY -> String -> IO ()
c_RegDeleteKey :: PKEY -> LPCTSTR -> IO ErrCode
regDeleteValue :: HKEY -> String -> IO ()
c_RegDeleteValue :: PKEY -> LPCTSTR -> IO ErrCode
mallocWideChars :: Int -> IO (Ptr a)
regEnumKeys :: HKEY -> IO [String]
regEnumKeyVals :: HKEY -> IO [(String, String, RegValueType)]
regEnumValue :: HKEY -> DWORD -> LPTSTR -> DWORD -> LPBYTE -> DWORD -> IO (RegValueType, String, Int)
c_RegEnumValue :: PKEY -> DWORD -> LPTSTR -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> LPBYTE -> Ptr DWORD -> IO ErrCode
regFlushKey :: HKEY -> IO ()
c_RegFlushKey :: PKEY -> IO ErrCode
regLoadKey :: HKEY -> String -> String -> IO ()
type RegNotifyOptions = DWORD
regNotifyChangeKeyValue :: HKEY -> Bool -> RegNotifyOptions -> HANDLE -> Bool -> IO ()
c_RegNotifyChangeKeyValue :: PKEY -> Bool -> RegNotifyOptions -> HANDLE -> Bool -> IO ErrCode
regOpenKey :: HKEY -> String -> IO HKEY
data RegInfoKey
RegInfoKey | |
|
regQueryInfoKey :: HKEY -> IO RegInfoKey
c_RegQueryInfoKey :: PKEY -> LPTSTR -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> Ptr DWORD -> Ptr FILETIME -> IO ErrCode
regQueryValueEx :: HKEY -> String -> LPBYTE -> Int -> IO RegValueType
type RegRestoreFlags = DWORD
regRestoreKey :: HKEY -> String -> RegRestoreFlags -> IO ()
c_RegRestoreKey :: PKEY -> LPCTSTR -> RegRestoreFlags -> IO ErrCode
regSaveKey :: HKEY -> String -> Maybe LPSECURITY_ATTRIBUTES -> IO ()
c_RegSaveKey :: PKEY -> LPCTSTR -> LPSECURITY_ATTRIBUTES -> IO ErrCode
regSetValue :: HKEY -> String -> String -> IO ()
type RegValueType = DWORD
regSetStringValue :: HKEY -> String -> String -> IO ()
regSetValueEx :: HKEY -> String -> RegValueType -> LPTSTR -> Int -> IO ()
c_RegSetValueEx :: PKEY -> LPCTSTR -> DWORD -> RegValueType -> LPTSTR -> Int -> IO ErrCode
regUnLoadKey :: HKEY -> String -> IO ()
c_RegUnLoadKey :: PKEY -> LPCTSTR -> IO ErrCode