{-# OPTIONS -fffi #-} {- JACK bindings for Haskell Copyright (C) 2007 Soenke Hahn This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA. -} module Sound.JACK.FFI where import Foreign.Ptr (Ptr, FunPtr) import Foreign.C.String (CString) import Foreign.C.Types (CUInt, CInt, CChar, CFloat, CULong) import Data.Bits (setBit, bit) import Data.Array(Ix) foreign import ccall "static jack/jack.h jack_client_open" client_open :: CString -> CULong -> Ptr CULong -> CString -> IO (Ptr ()) foreign import ccall "static jack/jack.h jack_client_new" client_new :: CString -> IO (Ptr ()) data OpenOptions = NoStartServer | UseExactName | ServerName deriving (Enum, Eq, Ord, Show, Ix) wordNullOption, wordNoStartServer, wordUseExactName, wordServerName :: CULong wordNullOption = 0 wordNoStartServer = flagToWord NoStartServer wordUseExactName = flagToWord UseExactName wordServerName = flagToWord ServerName data Status = Failure | InvalidOption | NameNotUnique | ServerStarted | ServerFailed | ServerError | NoSuchClient | LoadFailure | InitFailure | ShmFailure | VersionError deriving (Enum, Eq, Ord, Show, Ix) wordFailure, wordInvalidOption, wordNameNotUnique, wordServerStarted, wordServerFailed, wordServerError, wordNoSuchClient, wordLoadFailure, wordInitFailure, wordShmFailure, wordVersionError :: CULong wordFailure = flagToWord Failure wordInvalidOption = flagToWord InvalidOption wordNameNotUnique = flagToWord NameNotUnique wordServerStarted = flagToWord ServerStarted wordServerFailed = flagToWord ServerFailed wordServerError = flagToWord ServerError wordNoSuchClient = flagToWord NoSuchClient wordLoadFailure = flagToWord LoadFailure wordInitFailure = flagToWord InitFailure wordShmFailure = flagToWord ShmFailure wordVersionError = flagToWord VersionError foreign import ccall "static jack/jack.h jack_port_register" port_register :: Ptr () -> Ptr (CChar) -> Ptr (CChar) -> CULong -> CULong -> IO (Ptr ()) foreign import ccall "static jack/jack.h jack_set_process_callback" set_process_callback :: Ptr () -> FunPtr (CUInt -> Ptr (CChar) -> IO (CInt)) -> Ptr (CChar) -> IO (CInt) foreign import ccall "static jack/jack.h jack_port_get_buffer" port_get_buffer :: Ptr () -> CUInt -> IO (Ptr CFloat) foreign import ccall "static jack/jack.h jack_get_buffer_size" get_buffer_size :: Ptr () -> IO (CUInt) foreign import ccall "static jack/jack.h jack_activate" activate :: Ptr () -> IO (CInt) foreign import ccall "static jack/jack.h jack_client_close" client_close :: Ptr () -> IO (CInt) foreign import ccall "static jack/jack.h jack_get_ports" get_ports :: Ptr () -> Ptr (CChar) -> Ptr (CChar) -> CULong -> IO (Ptr (Ptr (CChar))) foreign import ccall "static jack/jack.h jack_connect" connect :: Ptr () -> Ptr (CChar) -> Ptr (CChar) -> IO (CInt) foreign import ccall "static jack/jack.h jack_port_unregister" port_unregister :: Ptr () -> Ptr () -> IO (CInt) foreign import ccall "static jack/jack.h jack_deactivate" deactivate :: Ptr () -> IO (CInt) -- * Utility functions flagToWord :: (Enum a) => a -> CULong flagToWord = bit . fromEnum flagsToWord :: (Enum a) => [a] -> CULong flagsToWord = foldl setBit 0 . map fromEnum wordToFlags :: (Enum a) => CULong -> [a] wordToFlags = map fst . filter (odd . snd) . zip [toEnum 0 ..] . iterate (flip div 2)