{-# LANGUAGE PackageImports #-}
module System.Win32.WindowsString.String
( LPSTR, LPCSTR, LPWSTR, LPCWSTR
, TCHAR, LPTSTR, LPCTSTR, LPCTSTR_
, withTString, withTStringLen, peekTString, peekTStringLen
, newTString
, withTStringBuffer, withTStringBufferLen
) where
import System.Win32.String hiding
( withTStringBuffer
, withTStringBufferLen
, withTString
, withTStringLen
, peekTString
, peekTStringLen
, newTString
)
import System.Win32.WindowsString.Types
import System.OsString.Internal.Types
#if MIN_VERSION_filepath(1,5,0)
import qualified "os-string" System.OsString.Data.ByteString.Short as SBS
#else
import qualified "filepath" System.OsPath.Data.ByteString.Short as SBS
#endif
import Data.Word (Word8)
withTStringBuffer :: Int -> (LPTSTR -> IO a) -> IO a
withTStringBuffer maxLength
= let dummyBuffer = WindowsString $ SBS.pack $ replicate (if even maxLength then maxLength else maxLength + 1) _nul
in withTString dummyBuffer
withTStringBufferLen :: Int -> ((LPTSTR, Int) -> IO a) -> IO a
withTStringBufferLen maxLength
= let dummyBuffer = WindowsString $ SBS.pack $ replicate (if even maxLength then maxLength else maxLength + 1) _nul
in withTStringLen dummyBuffer
_nul :: Word8
_nul = 0x00