On 2/25/13 5:31 PM, glen wrote:
mar...@snoutfarm.com wrote at 02/25/2013 02:57 PM:
Nope.  Monads are a purely functional construct.  A elegant generalization,
Arrows, enable one to construct Unix-style pipelines, but with typed
contracts.  That is, imagine having a command shell that rejected as bad
syntax pipelines where the data of the consumer and producer did not make
sense together.
You mean I wouldn't be allowed to listen to the smooth sounds of:

echo "main(t){for(t=0;;t++)putchar(t*((t>>9|t>>13)&25&t>>6));}" | gcc
-xc - && ./a.out | aplay
Here's an example taken from YampaSynth, a domain-specific language for sound synthesis built using the concepts of Functional Reactive Programming. The pipeline is all in Haskell, all the way to the OpenAL output. (No cheating with an external command line program.)

http://www.haskell.org/haskellwiki/Arrow
http://www.cs.rit.edu/~eca7215/frp-independent-study/Survey.pdf
http://www.haskell.org/haskellwiki/Yampa
http://hackage.haskell.org/package/YampaSynth

Here's a couple sounds. `scifi' is a whirly-gig sort of sound, and `scale' is just a set of sequential notes.
{-# LANGUAGE Arrows #-}

module Main where

import qualified SynthBasics as Synth
import qualified Data.Audio as Audio
import Player.OpenAL (play)
import FRP.Yampa

sciFi :: SF () Audio.Sample
sciFi = proc () -> do
  und   <- arr (*0.2) <<< Synth.oscSine 3.0  -< 0
  swp   <- arr (+1.0) <<< integral     -< -0.25
  audio <- Synth.oscSine 440           -< und + swp
  returnA -< audio

envBell :: SF (Event ()) (Synth.CV, Event ())
envBell = Synth.envGen 0 [(0.05,1),(1.5,0)] Nothing

bell :: Synth.Frequency -> SF () (Audio.Sample, Event ())
bell f = proc () -> do
  m            <- Synth.oscSine (2.33 * f)  -< 0
  audio        <- Synth.oscSine f           -< 2.0 * m
  (ampl, end)  <- envBell           -< noEvent
  returnA -< (audio * ampl, end)

scale :: SF () (Audio.Sample, Event ())
scale =  (  afterEach  [  (0.0, 60), (1.0, 62), (1.0, 64),
                          (1.0, 65), (1.0, 67), (1.0, 69),
                          (1.0, 71), (1.0, 72)]
            >>>  constant ()
                 &&& arr (fmap (\k -> (bell $ toFreq k) >>> arr fst))
            >>> rSwitch (constant 0))
         &&& after 8 ()

toFreq :: Int -> Double
toFreq n = 440.0 * (2.0 ** (((fromIntegral n) - 69.0) / 12.0))

main :: IO ()
main = do
  let playIt = play 44100 50000 1
  -- playIt (sciFi &&& after 5 ())
  playIt scale
  return()


============================================================
FRIAM Applied Complexity Group listserv
Meets Fridays 9a-11:30 at cafe at St. John's College
to unsubscribe http://redfish.com/mailman/listinfo/friam_redfish.com

Reply via email to