[Haskell-cafe] sound synthesis
Claude Heiland-Allen
claudiusmaximus at goto10.org
Fri May 2 06:21:25 EDT 2008
Thomas Girod wrote:
> Hi there. Following this advice
> (http://reddit.com/info/6hknz/comments/c03vdc7), I'm posting here.
>
>
> Recently, I read a few articles about Haskell (and FP in general) and
> music/sound.
>
> I remember an article ranting about how lazy evaluation would be great
> to do signal processing, but it was lacking real world example.
>
> I tried to do a little something about it, even though I'm still an
> haskell apprentice. So, here I come with a small bit of code, waiting
> for your insights to improve it.
>
> The task is to generate a sine wave and pipe it to /dev/dsp on my linux
> box. There is probably a nicer way to make some noise, like using SDL
> audio API bindings, but I didn't take the time to poke around this yet.
>
> So here it is :
>
>> module Main where
>
>> import qualified Data.ByteString as B
>> import Data.Word
>> import IO (stdout)
>
>> rate = 44100
>
>> sinusFloat :: [Float]
>> sinusFloat = map (\t -> (1 + sin (t*880*2*pi/rate)) / 2) [0..44099]
>
>> sinusWord :: [Word8]
>> sinusWord = map (\s -> floor (s * max)) sinusFloat
>> where max = 255
>
>> byte = B.pack sinusWord
>
>> main = B.hPut stdout byte
>
> It is supposed to generate a 880hz sine wav playing for one second, by
> typing ./bin > /dev/dsp, assuming your soundcard has a 44100hz
> samplingrate.
>
> /dev/dsp is supposed to receive its audio flux as an unsigned byte
> stream, that's why I'm converting my sine from [-1;1] to [0;1] and then
> to [0;255] Word8.
>
> However, I must miss something because the sound does not have the right
> frequency and is played too long. I guess the default sound format is
> 44100hz 16bits stereo, which would explain why it doesn't behave as
> expected.
Nope:
The default is 8-bit unsigned samples, using one channel (mono),
and an 8 kHz sampling rate.
http://www.oreilly.de/catalog/multilinux/excerpt/ch14-05.htm
Changing to rate = 8000 and sinusFloat = ... [0..rate-1] gives the
expected output.
> I'm wondering how I could convert a [Word16] to ByteString, and how I
> could use lazy evaluation to generate an infinite sine that stops with
> the interupt.
>
> Thomas
Claude
--
http://claudiusmaximus.goto10.org
More information about the Haskell-Cafe
mailing list