[commit: packages/Win32] Mistuke-fix-build, depend-os-windows, fix-appveyor-curl-ussue, issue-8-add-getUserName, master, win32-2.5.4.1-ghc-8.2, win32-prepare-release-2.4.0.0: Issue-8: Added getUserName (b53e40a)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:27:09 UTC 2017


Repository : ssh://git@git.haskell.org/Win32

On branches: Mistuke-fix-build,depend-os-windows,fix-appveyor-curl-ussue,issue-8-add-getUserName,master,win32-2.5.4.1-ghc-8.2,win32-prepare-release-2.4.0.0
Link       : http://git.haskell.org/packages/Win32.git/commitdiff/b53e40ae3dcd1147e4fafaf40f2e4db6f2d24961

>---------------------------------------------------------------

commit b53e40ae3dcd1147e4fafaf40f2e4db6f2d24961
Author: Tamar Christina <tamar at zhox.com>
Date:   Sat May 14 21:00:17 2016 +0200

    Issue-8: Added getUserName


>---------------------------------------------------------------

b53e40ae3dcd1147e4fafaf40f2e4db6f2d24961
 System/Win32/Info.hsc | 16 ++++++++++++++--
 1 file changed, 14 insertions(+), 2 deletions(-)

diff --git a/System/Win32/Info.hsc b/System/Win32/Info.hsc
index 81da6b2..3d725dd 100644
--- a/System/Win32/Info.hsc
+++ b/System/Win32/Info.hsc
@@ -21,12 +21,13 @@ module System.Win32.Info where
 
 import Control.Exception (catch)
 import Foreign.Marshal.Alloc (alloca)
+import Foreign.Marshal.Utils (with)
 import Foreign.Marshal.Array (allocaArray)
 import Foreign.Ptr (Ptr, nullPtr)
 import Foreign.Storable (Storable(..))
 import System.IO.Error (isDoesNotExistError)
-import System.Win32.Types (DWORD, LPCTSTR, LPTSTR, LPVOID, UINT, WORD)
-import System.Win32.Types (failIfZero, peekTStringLen, withTString)
+import System.Win32.Types (DWORD, LPDWORD, LPCTSTR, LPTSTR, LPVOID, UINT, WORD)
+import System.Win32.Types (failIfZero, failIfFalse_, peekTStringLen, withTString)
 
 #if !MIN_VERSION_base(4,6,0)
 import Prelude hiding (catch)
@@ -352,6 +353,17 @@ type SMSetting = UINT
 
 -- %fun GetUserName :: IO String
 
+foreign import WINDOWS_CCONV unsafe "windows.h GetUserNameW"
+  c_GetUserName :: LPTSTR -> LPDWORD -> IO Bool
+  
+getUserName :: IO String
+getUserName =     
+  allocaArray 512 $ \ c_str -> 
+    with 512 $ \ c_len -> do
+        failIfFalse_ "GetUserName" $ c_GetUserName c_str c_len
+        len <- peek c_len
+        peekTStringLen (c_str, fromIntegral len - 1)
+
 ----------------------------------------------------------------
 -- Version Info
 ----------------------------------------------------------------



More information about the ghc-commits mailing list