{-# 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
= forall a. String -> (LPTSTR -> IO a) -> IO a
withTString String
cmd forall a b. (a -> b) -> a -> b
$ \LPTSTR
sendCmd -> do
MCIERROR
err <- LPTSTR -> LPTSTR -> MCIERROR -> HANDLE -> IO MCIERROR
c_mciSendString LPTSTR
sendCmd forall a. Ptr a
nullPtr MCIERROR
0 forall a. Ptr a
nullPtr
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (MCIERROR
err forall a. Eq a => a -> a -> Bool
== MCIERROR
0)
forall a b. (a -> b) -> a -> b
$ MCIERROR -> IO ()
mciGetErrorString MCIERROR
err
foreign import WINDOWS_CCONV safe "windows.h mciSendStringW"
c_mciSendString :: LPCTSTR -> LPTSTR -> UINT -> HANDLE -> IO MCIERROR
mciGetErrorString :: MCIERROR -> IO ()
mciGetErrorString :: MCIERROR -> IO ()
mciGetErrorString MCIERROR
err
= forall a. Int -> ((LPTSTR, Int) -> IO a) -> IO a
withTStringBufferLen Int
256 forall a b. (a -> b) -> a -> b
$ \(LPTSTR
cstr, Int
len) -> do
String -> IO Bool -> IO ()
failIfFalse_ ([String] -> String
unwords [String
"mciGetErrorString", forall a. Show a => a -> String
show MCIERROR
err]) forall a b. (a -> b) -> a -> b
$
MCIERROR -> LPTSTR -> MCIERROR -> IO Bool
c_mciGetErrorString MCIERROR
err LPTSTR
cstr forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len
String
msg <- LPTSTR -> IO String
peekTString LPTSTR
cstr
MCIERROR
cp <- IO MCIERROR
getCurrentCodePage
forall a. IOError -> IO a
ioError forall a b. (a -> b) -> a -> b
$ String -> IOError
userError forall a b. (a -> b) -> a -> b
$ MCIERROR -> String -> String
encodeMultiByte MCIERROR
cp String
msg
foreign import WINDOWS_CCONV unsafe "windows.h mciGetErrorStringW"
c_mciGetErrorString :: MCIERROR -> LPTSTR -> UINT -> IO BOOL