
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. 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

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

On Fri, 2 May 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.
There are some 'real world examples', however speed is currently the factor which limits the fun. Currently you get immediate results with the SuperCollider interface or with the CSound interface of Haskore: http://www.haskell.org/haskellwiki/Applications_and_libraries/Music_and_soun... Cf. Haskell Art mailing list: http://lists.lurk.org/mailman/listinfo/haskell-art
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.
I'm wondering how I could convert a [Word16] to ByteString,
With Data.Binary.
and how I could use lazy evaluation to generate an infinite sine that stops with the interupt.
So far I used a really silly way, but it worked for me so far: I start 'play' from SOX package and pipe my signal into it: http://darcs.haskell.org/synthesizer/src/Sox/Play.hs

Thomas Girod:
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.
Check (e.g. through Google) what Henning Thielemann wrote about. I can offer you something written not in Haskell, but in Clean (the conversion to Haskell is largely trivial), see e.g. this PADL paper, I have it on-line: http://users.info.unicaen.fr/~karczma/arpap/cleasyn.pdf
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.
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.
"Infinite sine that stops" is a bit contradictory. In my view the solution is the following. You generate your infinite whatever. Sine, Karplus-Strong sound, flute, whatever, you combine all in one infinite stream, and you don't care at all about stopping. [In Clean I used unboxed, spine-lazy, but head-strict lists. The format was floating-point]. THEN, during the conversion, piping, construction of a .wav table (vector) you think about the time-limitation of the stream. I played with static constraints (concrete number of converted samples). If you want to do it dynamically, then, either you know how to interrupt *any* infinite process within Haskell, or you have to learn how to do it... Here people more competent than myself will surely help you. Good luck, and thanks for your interest in a this fabulous field. Jerzy Karczmarczuk

On May 2, 2008, at 2:58 AM, Thomas Girod wrote:
I remember an article ranting about how lazy evaluation would be great to do signal processing, but it was lacking real world example.
I did something similar a few weeks ago. I used libmad to lazily decode an MP3 file and play it using OS/X's core audio. Here's that post, with links to the libmad bindings (which might be useful for you, even if the CoreAudio isn't.) chris http://www.haskell.org/pipermail/haskell-cafe/2008-March/040796.html
participants (6)
-
Chris Waterson
-
Claude Heiland-Allen
-
Evan Laforge
-
Henning Thielemann
-
jerzy.karczmarczuk@info.unicaen.fr
-
Thomas Girod