{-# LANGUAGE PackageImports #-}

{- |
   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.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)

-- | 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 :: WindowsString
dummyBuffer = ShortByteString -> WindowsString
WindowsString (ShortByteString -> WindowsString)
-> ShortByteString -> WindowsString
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
SBS.pack ([Word8] -> ShortByteString) -> [Word8] -> ShortByteString
forall a b. (a -> b) -> a -> b
$ Int -> Word8 -> [Word8]
forall a. Int -> a -> [a]
replicate (if Int -> Bool
forall a. Integral a => a -> Bool
even Int
maxLength then Int
maxLength else Int
maxLength Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word8
_nul
    in  WindowsString -> (LPTSTR -> IO a) -> IO a
forall a. WindowsString -> (LPTSTR -> IO a) -> IO a
withTString WindowsString
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 :: WindowsString
dummyBuffer = ShortByteString -> WindowsString
WindowsString (ShortByteString -> WindowsString)
-> ShortByteString -> WindowsString
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
SBS.pack ([Word8] -> ShortByteString) -> [Word8] -> ShortByteString
forall a b. (a -> b) -> a -> b
$ Int -> Word8 -> [Word8]
forall a. Int -> a -> [a]
replicate (if Int -> Bool
forall a. Integral a => a -> Bool
even Int
maxLength then Int
maxLength else Int
maxLength Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word8
_nul
    in  WindowsString -> ((LPTSTR, Int) -> IO a) -> IO a
forall a. WindowsString -> ((LPTSTR, Int) -> IO a) -> IO a
withTStringLen WindowsString
dummyBuffer


_nul :: Word8
_nul :: Word8
_nul = Word8
0x00