wahsp-0.2: A haskell binding of the Web Audio API ala blank-canvas

LicenseBSD(see LICENSE file)
MaintainerNicholas Shaheed
StabilityAlpha
Safe HaskellNone
LanguageHaskell2010

Web.Audio

Contents

Description

wahsp (Web Audio HaSkell Protocol) is a binding for Haskell to the Web Audio API ala blank-canvas. Audio sources, effects, etc. can be combined, manipulated, and otherwise controlled using haskell and are then rendered in the the browser (see the above link for browser compatibility).

Synopsis

Set-Up

webAudio :: WAOptions -> (Document -> IO ()) -> IO () Source #

webAudio is the starting point for connecting and interacting with the API. A simple example of how to use this is:

 module Main where
 import Web.Audio
 
 main :: IO ()
 main = do
   webAudio 3000 $ \doc -> do
     send doc $ do
       osc1  <- createOscillator 200 0 Sine -- create an OscillatorNode
       gain1 <- createGain 0.5              -- create a GainNode
 
       connect $ osc1 .|. gain1 .||. eCtx   -- connect these nodes together, and then connect them to the audio context
 
       start osc1 -- make sounds!

When running, go to http://localhost:3000/ in a browser to hear a 200Hz sine wave!

More examples can be found here.

data WAOptions Source #

Various options when sending info to the browser

Constructors

WAOptions 

Fields

Connecting nodes, params, and the audio context

The Web Audio API is comprised of nodes (AudioNodes, AudioParams, and the AudioContext) that are connected, input to output, to form a chain comprised of sources, effects, and a destination.

This chain is typically organized as a source -> effects -> destination, where destination is either the AudioContext (if you actually want to produce sound in this chain), some AudioParam (if you want to control a param with an audio signal, e.g. a low-frequency oscillator (lfo)), or some AudioNode.

To chain together AudioNodes and AudioParams, use .|. and end the chain with .||. For example:

osc1  <- createOscillator 200 0 Sine
gain1 <- createGain 0.5

connect $ osc1 .|. gain1 .||. eCtx
start osc1

See the official docs for a more detailed overview.

connect :: AudioGraph AudNode b -> WebAudio () Source #

Connects the AudioGraph chain (made by connecting AudioNodes, AudioParams, and AudioContexts with .|. and .||.)

(.|.) :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b infix 7 Source #

Connect the front of the chain of nodes together, end the chain with .||.

(.||.) :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b infix 8 Source #

End the chain of AudioNodes.

To end the chain at the audio context:

connect $ osc1 .|. gain1 .||. eCtx

To end with an AudioParam (that is located in the AudioNode gain1):

connect $ osc1 .|. gain1 .||. eParam (gain gain1)

To end with the AudioNode gain1:

connect $ osc1 .|. gain1 .||. eNode gain1

connector :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b Source #

function implementation of .|.

connectorLast :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b Source #

function implementation of .||.

eNode :: AudioNode a => a -> AudioGraph AudNode AudNode Source #

Set the ending node to an AudioNode

eCtx :: AudioGraph AudNode AudioContext Source #

Set the ending node to the AudioContext

Data Types

newtype WebAudio a Source #

Contains the commands and procedures to be sent to the web browser

Constructors

WebAudio (RemoteMonad Command Procedure a) 

Instances

Monad WebAudio Source # 

Methods

(>>=) :: WebAudio a -> (a -> WebAudio b) -> WebAudio b #

(>>) :: WebAudio a -> WebAudio b -> WebAudio b #

return :: a -> WebAudio a #

fail :: String -> WebAudio a #

Functor WebAudio Source # 

Methods

fmap :: (a -> b) -> WebAudio a -> WebAudio b #

(<$) :: a -> WebAudio b -> WebAudio a #

Applicative WebAudio Source # 

Methods

pure :: a -> WebAudio a #

(<*>) :: WebAudio (a -> b) -> WebAudio a -> WebAudio b #

(*>) :: WebAudio a -> WebAudio b -> WebAudio b #

(<*) :: WebAudio a -> WebAudio b -> WebAudio a #

Semigroup a => Semigroup (WebAudio a) Source # 

Methods

(<>) :: WebAudio a -> WebAudio a -> WebAudio a #

sconcat :: NonEmpty (WebAudio a) -> WebAudio a #

stimes :: Integral b => b -> WebAudio a -> WebAudio a #

Monoid a => Monoid (WebAudio a) Source # 

Methods

mempty :: WebAudio a #

mappend :: WebAudio a -> WebAudio a -> WebAudio a #

mconcat :: [WebAudio a] -> WebAudio a #

data OscillatorNode Source #

OscillatorNode represents a periodic waveform with a frequency (in hertz), detuning (in cents), an OscillatorNodeType (e.g. a sine wave, square wave, etc.), etc.

Constructors

OscillatorNode 

Fields

Procedures

Instantiation functions

createOscillator Source #

Arguments

:: Double

Frequency (in hertz)

-> Double

Detuning (in cents)

-> OscillatorNodeType

Waveform type

-> WebAudio OscillatorNode 

creates an oscillator with a frequency (in hertz), a detuning value (in cents), and an OscillatorNodeType (e.g. a sine wave, square wave, etc.)

createGain :: Double -> WebAudio GainNode Source #

Create a gain node with a gain value, typically between 0.0 and 1.0

Other Procedures

audioContext :: AudioContext Source #

A function that returns an AudioContext

maxValue :: AudioParam -> WebAudio Double Source #

Get the maximum value of an AudioParam

minValue :: AudioParam -> WebAudio Double Source #

Get the minimum value of an AudioParam

value :: AudioParam -> WebAudio Double Source #

Get the current value of an AudioParam

currentTime :: WebAudio Double Source #

Get the current time in the sessions (in seconds). This represents the amount of time that has passed since the session was instantiated

Playback control

OscillatorNode specific playback controls

start :: OscillatorNode -> WebAudio () Source #

Immediately start playback of an OscillatorNode

startWhen :: OscillatorNode -> Double -> WebAudio () Source #

Start playing an OscillatorNode at t seconds. If t has already passed, it will immediately stop

stop :: OscillatorNode -> WebAudio () Source #

Immediately stop playback of an OscillatorNode

stopWhen :: OscillatorNode -> Double -> WebAudio () Source #

Stop playing an OscillatorNode at t seconds. If t has already passed, it will immediately stop

Disconnecting functions

disconnect :: AudioNode a => a -> WebAudio () Source #

Disconnect all outgoing connections from AudioNode n

disconnectOutput :: AudioNode a => a -> Int -> WebAudio () Source #

Disconnect a specific output

Change AudioParam value

Different functions for altering the values of AudioParams (immediately, ramping, etc.)