{- |
   Module      :  System.Win32.String
   Copyright   :  2013 shelarcy
   License     :  BSD-style

   Maintainer  :  shelarcy@gmail.com
   Stability   :  Provisional
   Portability :  Non-portable (Win32 API)

   Utilities for primitive marshalling of Windows' C strings.
-}
module System.Win32.String
  ( LPSTR, LPCSTR, LPWSTR, LPCWSTR
  , TCHAR, LPTSTR, LPCTSTR, LPCTSTR_
  , withTString, withTStringLen, peekTString, peekTStringLen
  , newTString
  , withTStringBuffer, withTStringBufferLen
  ) where
import System.Win32.Types

-- | Marshal a dummy Haskell string into a NUL terminated C wide string

-- using temporary storage.

--

-- * the Haskell string is created by length parameter. And the Haskell

--   string contains /only/ NUL characters.

--

-- * the memory is freed when the subcomputation terminates (either

--   normally or via an exception), so the pointer to the temporary

--   storage must /not/ be used after this.

--

withTStringBuffer :: Int -> (LPTSTR -> IO a) -> IO a
withTStringBuffer :: forall a. Int -> (LPTSTR -> IO a) -> IO a
withTStringBuffer Int
maxLength
  = let dummyBuffer :: [Char]
dummyBuffer = Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate Int
maxLength Char
'\0'
    in  [Char] -> (LPTSTR -> IO a) -> IO a
forall a. [Char] -> (LPTSTR -> IO a) -> IO a
withTString [Char]
dummyBuffer

-- | Marshal a dummy Haskell string into a C wide string (i.e. wide

-- character array) in temporary storage, with explicit length

-- information.

--

-- * the Haskell string is created by length parameter. And the Haskell

--   string contains /only/ NUL characters.

--

-- * the memory is freed when the subcomputation terminates (either

--   normally or via an exception), so the pointer to the temporary

--   storage must /not/ be used after this.

--

withTStringBufferLen :: Int -> ((LPTSTR, Int) -> IO a) -> IO a
withTStringBufferLen :: forall a. Int -> ((LPTSTR, Int) -> IO a) -> IO a
withTStringBufferLen Int
maxLength
  = let dummyBuffer :: [Char]
dummyBuffer = Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate Int
maxLength Char
'\0'
    in  [Char] -> ((LPTSTR, Int) -> IO a) -> IO a
forall a. [Char] -> ((LPTSTR, Int) -> IO a) -> IO a
withTStringLen [Char]
dummyBuffer