Hello, I am trying to write a Haskell program that plays wav files using
foreign import on the Win32 function PlaySound:

BOOL PlaySound(
    LPCTSTR pszSound,
    HMODULE hmod,
    DWORD fdwSound
);

I wrote the following module to import the function, which I successfully
compiled with GHC using “ghc --make Sound.hs” (much of this module is
adapted from someone else’s code)

--Sound.hs
{-# LANGUAGE ForeignFunctionInterface #-}

module Sound
        where

import Foreign
import Foreign.C
import CString
import System.IO
import Data.Bits
import System.Win32

data SoundFlag
  = Async
  | Filename
  | Sync
  deriving ()

--I found these values online
marshall_SoundFlag :: SoundFlag -> Int32
marshall_SoundFlag arg1 = 
  case arg1 of 
     Async       -> 0
     Sync        -> 1
     Filename    -> 131072


foreign import ccall "PlaySound" play :: CString -> Int32 -> Int32 -> IO
Bool

playSound :: String -> Int32 -> SoundFlag -> IO Bool
playSound filename hmod flag = play (unsafePerformIO (newCString filename))
hmod (marshall_SoundFlag flag)



Then I wrote the following to test it:

--testSound.hs
{-# LANGUAGE ForeignFunctionInterface #-}

import Sound

main = do
        x <- playSound "test.wav" 0 Filename
        print x



When I load the test program in ghci, it loads properly.  When I run main,
it successfully plays the sound, then prints “True” and then crashes.  Every
time.  
When I try to compile the test program, I get the following error message:

Linking testSound.exe ...
.\Sound.o:fake:(.text+0x50): undefined reference to 'PlaySound'
.\Sound.o:fake:(.text+0x5a2): undefined reference to 'PlaySound'
collect2: ld returned 1 exit status

I'm wondering if their is a problem with the way I converted data from
haskell to C.  I'm also concerned that my GHC compiler is not set up
properly for this type of program.  GHCi seems to be unable to figure out
what PlaySound is supposed to be until Sound.hs is compiled, at which point
it plays the sound but then crashes.  Any help would be appreciated.  
-- 
View this message in context: 
http://old.nabble.com/foreign-import-PlaySound-causing-GHCi-to-crash-tp27414694p27414694.html
Sent from the Haskell - Glasgow-haskell-bugs mailing list archive at Nabble.com.

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to