module System.Win32.WindowsString.Utils
( module System.Win32.WindowsString.Utils
, module System.Win32.Utils
) where
import Foreign.C.Types ( CInt )
import Foreign.Marshal.Array ( allocaArray )
import Foreign.Ptr ( nullPtr )
import System.Win32.Utils hiding
( try
, tryWithoutNull
, trySized
)
import System.Win32.WindowsString.String ( LPTSTR, peekTString, peekTStringLen
, withTStringBufferLen )
import System.Win32.WindowsString.Types ( UINT
, failIfZero
)
import qualified System.Win32.WindowsString.Types ( try )
import System.OsString.Windows
try :: String -> (LPTSTR -> UINT -> IO UINT) -> UINT -> IO WindowsString
try = System.Win32.WindowsString.Types.try
{-# INLINE try #-}
tryWithoutNull :: String -> (LPTSTR -> UINT -> IO UINT) -> UINT -> IO WindowsString
tryWithoutNull loc f n = do
e <- allocaArray (fromIntegral n) $ \lptstr -> do
r <- failIfZero loc $ f lptstr n
if r > n then return (Left r) else do
str <- peekTString lptstr
return (Right str)
case e of
Left r' -> tryWithoutNull loc f r'
Right str -> return str
trySized :: String -> (LPTSTR -> CInt -> IO CInt) -> IO WindowsString
trySized wh f = do
c_len <- failIfZero wh $ f nullPtr 0
let len = fromIntegral c_len
withTStringBufferLen len $ \(buf', len') -> do
let c_len' = fromIntegral len'
c_len'' <- failIfZero wh $ f buf' c_len'
let len'' = fromIntegral c_len''
peekTStringLen (buf', len'' - 1)