{-# LANGUAGE CPP #-}
module Media.Win32
( module Media.Win32
) where
import Control.Monad ( unless )
import Prelude hiding ( ioError, userError )
import System.IO.Error ( ioError, userError )
import System.Win32.Encoding ( encodeMultiByte, getCurrentCodePage )
import System.Win32.Types
import System.Win32.String ( withTStringBufferLen )
type MCIERROR = DWORD
#include "windows_cconv.h"
mciSendString :: String -> IO ()
mciSendString :: String -> IO ()
mciSendString String
cmd
= String -> (LPTSTR -> IO ()) -> IO ()
forall a. String -> (LPTSTR -> IO a) -> IO a
withTString String
cmd ((LPTSTR -> IO ()) -> IO ()) -> (LPTSTR -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \LPTSTR
sendCmd -> do
err <- LPTSTR -> LPTSTR -> UINT -> HANDLE -> IO UINT
c_mciSendString LPTSTR
sendCmd LPTSTR
forall a. Ptr a
nullPtr UINT
0 HANDLE
forall a. Ptr a
nullPtr
unless (err == 0)
$ mciGetErrorString err
foreign import WINDOWS_CCONV safe "windows.h mciSendStringW"
c_mciSendString :: LPCTSTR -> LPTSTR -> UINT -> HANDLE -> IO MCIERROR
mciGetErrorString :: MCIERROR -> IO ()
mciGetErrorString :: UINT -> IO ()
mciGetErrorString UINT
err
= Int -> ((LPTSTR, Int) -> IO ()) -> IO ()
forall a. Int -> ((LPTSTR, Int) -> IO a) -> IO a
withTStringBufferLen Int
256 (((LPTSTR, Int) -> IO ()) -> IO ())
-> ((LPTSTR, Int) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(LPTSTR
cstr, Int
len) -> do
String -> IO Bool -> IO ()
failIfFalse_ ([String] -> String
unwords [String
"mciGetErrorString", UINT -> String
forall a. Show a => a -> String
show UINT
err]) (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$
UINT -> LPTSTR -> UINT -> IO Bool
c_mciGetErrorString UINT
err LPTSTR
cstr (UINT -> IO Bool) -> UINT -> IO Bool
forall a b. (a -> b) -> a -> b
$ Int -> UINT
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len
msg <- LPTSTR -> IO String
peekTString LPTSTR
cstr
cp <- getCurrentCodePage
ioError $ userError $ encodeMultiByte cp msg
foreign import WINDOWS_CCONV unsafe "windows.h mciGetErrorStringW"
c_mciGetErrorString :: MCIERROR -> LPTSTR -> UINT -> IO BOOL