module Sound.RubberBand.Raw
( Stretcher(..)
, SampleRate, NumChannels, TimeRatio, PitchScale
, new, delete, p_delete, reset
, setTimeRatio, setPitchScale
, getTimeRatio, getPitchScale
, getLatency
, setTransientsOption
, setDetectorOption
, setPhaseOption
, setFormantOption
, setPitchOption
, setExpectedInputDuration
, getSamplesRequired
, setMaxProcessSize
, setKeyFrameMap
, study, process
, available, retrieve
, getChannelCount
, calculateStretch
, setDebugLevel
, setDefaultDebugLevel
) where
import Foreign.Ptr (Ptr, FunPtr)
import Foreign.C.Types
import Foreign.Marshal.Utils (fromBool)
import Sound.RubberBand.Option
fromOptions' :: (Integral a) => Options -> a
fromOptions' = fromIntegral . fromOptions
optionEnum' :: (Option o, Integral a) => o -> a
optionEnum' = fromIntegral . optionEnum
newtype Stretcher = Stretcher (Ptr (Stretcher))
type SampleRate = Int
type NumChannels = Int
type TimeRatio = Double
type PitchScale = Double
new :: (SampleRate) -> (NumChannels) -> (Options) -> (TimeRatio) -> (PitchScale) -> IO ((Stretcher))
new a1 a2 a3 a4 a5 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromOptions' a3} in
let {a4' = realToFrac a4} in
let {a5' = realToFrac a5} in
new'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = id res} in
return (res')
delete :: (Stretcher) -> IO ()
delete a1 =
let {a1' = id a1} in
delete'_ a1' >>
return ()
foreign import ccall "&rubberband_delete"
p_delete :: FunPtr (Ptr Stretcher -> IO ())
reset :: (Stretcher) -> IO ()
reset a1 =
let {a1' = id a1} in
reset'_ a1' >>
return ()
setTimeRatio :: (Stretcher) -> (TimeRatio) -> IO ()
setTimeRatio a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
setTimeRatio'_ a1' a2' >>
return ()
setPitchScale :: (Stretcher) -> (PitchScale) -> IO ()
setPitchScale a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
setPitchScale'_ a1' a2' >>
return ()
getTimeRatio :: (Stretcher) -> IO ((TimeRatio))
getTimeRatio a1 =
let {a1' = id a1} in
getTimeRatio'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
getPitchScale :: (Stretcher) -> IO ((PitchScale))
getPitchScale a1 =
let {a1' = id a1} in
getPitchScale'_ a1' >>= \res ->
let {res' = realToFrac res} in
return (res')
getLatency :: (Stretcher) -> IO ((Int))
getLatency a1 =
let {a1' = id a1} in
getLatency'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
setTransientsOption :: (Stretcher) -> (Transients) -> IO ()
setTransientsOption a1 a2 =
let {a1' = id a1} in
let {a2' = optionEnum' a2} in
setTransientsOption'_ a1' a2' >>
return ()
setDetectorOption :: (Stretcher) -> (Detector) -> IO ()
setDetectorOption a1 a2 =
let {a1' = id a1} in
let {a2' = optionEnum' a2} in
setDetectorOption'_ a1' a2' >>
return ()
setPhaseOption :: (Stretcher) -> (Phase) -> IO ()
setPhaseOption a1 a2 =
let {a1' = id a1} in
let {a2' = optionEnum' a2} in
setPhaseOption'_ a1' a2' >>
return ()
setFormantOption :: (Stretcher) -> (Formant) -> IO ()
setFormantOption a1 a2 =
let {a1' = id a1} in
let {a2' = optionEnum' a2} in
setFormantOption'_ a1' a2' >>
return ()
setPitchOption :: (Stretcher) -> (Pitch) -> IO ()
setPitchOption a1 a2 =
let {a1' = id a1} in
let {a2' = optionEnum' a2} in
setPitchOption'_ a1' a2' >>
return ()
setExpectedInputDuration :: (Stretcher) -> (Int) -> IO ()
setExpectedInputDuration a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
setExpectedInputDuration'_ a1' a2' >>
return ()
getSamplesRequired :: (Stretcher) -> IO ((Int))
getSamplesRequired a1 =
let {a1' = id a1} in
getSamplesRequired'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
setMaxProcessSize :: (Stretcher) -> (Int) -> IO ()
setMaxProcessSize a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
setMaxProcessSize'_ a1' a2' >>
return ()
setKeyFrameMap :: (Stretcher) -> (Int) -> (Ptr CUInt) -> (Ptr CUInt) -> IO ()
setKeyFrameMap a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = id a3} in
let {a4' = id a4} in
setKeyFrameMap'_ a1' a2' a3' a4' >>
return ()
study :: (Stretcher) -> (Ptr (Ptr CFloat)) -> (Int) -> (Bool) -> IO ()
study a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromBool a4} in
study'_ a1' a2' a3' a4' >>
return ()
process :: (Stretcher) -> (Ptr (Ptr CFloat)) -> (Int) -> (Bool) -> IO ()
process a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromBool a4} in
process'_ a1' a2' a3' a4' >>
return ()
available :: (Stretcher) -> IO ((Int))
available a1 =
let {a1' = id a1} in
available'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
retrieve :: (Stretcher) -> (Ptr (Ptr CFloat)) -> (Int) -> IO ((Int))
retrieve a1 a2 a3 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = fromIntegral a3} in
retrieve'_ a1' a2' a3' >>= \res ->
let {res' = fromIntegral res} in
return (res')
getChannelCount :: (Stretcher) -> IO ((Int))
getChannelCount a1 =
let {a1' = id a1} in
getChannelCount'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
calculateStretch :: (Stretcher) -> IO ()
calculateStretch a1 =
let {a1' = id a1} in
calculateStretch'_ a1' >>
return ()
setDebugLevel :: (Stretcher) -> (Int) -> IO ()
setDebugLevel a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
setDebugLevel'_ a1' a2' >>
return ()
setDefaultDebugLevel :: (Int) -> IO ()
setDefaultDebugLevel a1 =
let {a1' = fromIntegral a1} in
setDefaultDebugLevel'_ a1' >>
return ()
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_new"
new'_ :: (CUInt -> (CUInt -> (CInt -> (CDouble -> (CDouble -> (IO (Stretcher)))))))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_delete"
delete'_ :: ((Stretcher) -> (IO ()))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_reset"
reset'_ :: ((Stretcher) -> (IO ()))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_time_ratio"
setTimeRatio'_ :: ((Stretcher) -> (CDouble -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_pitch_scale"
setPitchScale'_ :: ((Stretcher) -> (CDouble -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_get_time_ratio"
getTimeRatio'_ :: ((Stretcher) -> (IO CDouble))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_get_pitch_scale"
getPitchScale'_ :: ((Stretcher) -> (IO CDouble))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_get_latency"
getLatency'_ :: ((Stretcher) -> (IO CUInt))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_transients_option"
setTransientsOption'_ :: ((Stretcher) -> (CInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_detector_option"
setDetectorOption'_ :: ((Stretcher) -> (CInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_phase_option"
setPhaseOption'_ :: ((Stretcher) -> (CInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_formant_option"
setFormantOption'_ :: ((Stretcher) -> (CInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_pitch_option"
setPitchOption'_ :: ((Stretcher) -> (CInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_expected_input_duration"
setExpectedInputDuration'_ :: ((Stretcher) -> (CUInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_get_samples_required"
getSamplesRequired'_ :: ((Stretcher) -> (IO CUInt))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_max_process_size"
setMaxProcessSize'_ :: ((Stretcher) -> (CUInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_key_frame_map"
setKeyFrameMap'_ :: ((Stretcher) -> (CUInt -> ((Ptr CUInt) -> ((Ptr CUInt) -> (IO ())))))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_study"
study'_ :: ((Stretcher) -> ((Ptr (Ptr CFloat)) -> (CUInt -> (CInt -> (IO ())))))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_process"
process'_ :: ((Stretcher) -> ((Ptr (Ptr CFloat)) -> (CUInt -> (CInt -> (IO ())))))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_available"
available'_ :: ((Stretcher) -> (IO CInt))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_retrieve"
retrieve'_ :: ((Stretcher) -> ((Ptr (Ptr CFloat)) -> (CUInt -> (IO CUInt))))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_get_channel_count"
getChannelCount'_ :: ((Stretcher) -> (IO CUInt))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_calculate_stretch"
calculateStretch'_ :: ((Stretcher) -> (IO ()))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_debug_level"
setDebugLevel'_ :: ((Stretcher) -> (CInt -> (IO ())))
foreign import ccall safe "Sound/RubberBand/Raw.chs.h rubberband_set_default_debug_level"
setDefaultDebugLevel'_ :: (CInt -> (IO ()))