License | BSD(see LICENSE file) |
---|---|
Maintainer | Nicholas Shaheed |
Stability | Alpha |
Safe Haskell | None |
Language | Haskell2010 |
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).
- webAudio :: WAOptions -> (Document -> IO ()) -> IO ()
- data WAOptions = WAOptions {}
- send :: Document -> WebAudio a -> IO a
- connect :: AudioGraph AudNode b -> WebAudio ()
- (.|.) :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b
- (.||.) :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b
- connector :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b
- connectorLast :: forall b a. AudioNode a => a -> AudioGraph AudNode b -> AudioGraph AudNode b
- eNode :: AudioNode a => a -> AudioGraph AudNode AudNode
- eParam :: AudioParam -> AudioGraph AudNode AudioParam
- eCtx :: AudioGraph AudNode AudioContext
- newtype WebAudio a = WebAudio (RemoteMonad Command Procedure a)
- class JSArg a => AudioNode a where
- data OscillatorNode = OscillatorNode {}
- data OscillatorNodeType
- data GainNode = GainNode {}
- data AudioParam = AudioParam AudioParamType Int
- data ChannelCountMode :: * where
- data AudioParamType
- createOscillator :: Double -> Double -> OscillatorNodeType -> WebAudio OscillatorNode
- createGain :: Double -> WebAudio GainNode
- audioContext :: AudioContext
- maxValue :: AudioParam -> WebAudio Double
- minValue :: AudioParam -> WebAudio Double
- value :: AudioParam -> WebAudio Double
- currentTime :: WebAudio Double
- start :: OscillatorNode -> WebAudio ()
- startWhen :: OscillatorNode -> Double -> WebAudio ()
- stop :: OscillatorNode -> WebAudio ()
- stopWhen :: OscillatorNode -> Double -> WebAudio ()
- disconnect :: AudioNode a => a -> WebAudio ()
- disconnectOutput :: AudioNode a => a -> Int -> WebAudio ()
- disconnectOutputInput :: AudioNode a => a -> a -> Int -> Int -> WebAudio ()
- disconnectDestNode :: AudioNode a => a -> a -> WebAudio ()
- disconnectDestNodeSpec :: AudioNode a => a -> a -> Int -> WebAudio ()
- disconnectDestParam :: AudioNode a => a -> AudioParam -> WebAudio ()
- disconnectDestParamSpec :: AudioNode a => a -> AudioParam -> Int -> WebAudio ()
- setValue :: AudioParam -> Double -> WebAudio ()
- setValueAtTime :: AudioParam -> Double -> Double -> WebAudio ()
- linearRampToValueAtTime :: AudioParam -> Double -> Double -> WebAudio ()
- exponentialRampToValueAtTime :: AudioParam -> Double -> Double -> WebAudio ()
- setTargetAtTime :: AudioParam -> Double -> Double -> Double -> WebAudio ()
- cancelScheduledValues :: AudioParam -> Double -> WebAudio ()
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 = dowebAudio
3000 $ \doc -> dosend
doc $ do osc1 <-createOscillator
200 0Sine
-- create anOscillatorNode
gain1 <-createGain
0.5 -- create aGainNode
connect
$ osc1.|.
gain1.||.
eCtx
-- connect these nodes together, and then connect them to the audio contextstart
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.
Various options when sending info to the browser
Constructors
WAOptions | |
Connecting nodes, params, and the audio context
The Web Audio API is comprised of nodes (AudioNode
s, AudioParam
s, 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 AudioNode
s and AudioParam
s, use .|.
and end the chain with .||.
For example:
osc1 <-createOscillator
200 0Sine
gain1 <-createGain
0.5connect
$ 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 AudioNode
s, AudioParam
s, and AudioContext
s
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 AudioNode
s.
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 .||.
eParam :: AudioParam -> AudioGraph AudNode AudioParam Source #
Set the ending node to an AudioParam
eCtx :: AudioGraph AudNode AudioContext Source #
Set the ending node to the AudioContext
Data Types
Contains the commands and procedures to be sent to the web browser
class JSArg a => AudioNode a where Source #
And AudioNode is an interface for any audio processing module in the Web Audio API
Minimal complete definition
numberOfInputs, numberOfOutputs, channelCount, channelCountMode, channelInterpretation
Methods
numberOfInputs :: a -> Int Source #
numberOfOutputs :: a -> Int Source #
channelCount :: a -> Int Source #
channelCountMode :: a -> ChannelCountMode Source #
channelInterpretation :: a -> ChannelInterpretation Source #
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
|
Instances
Eq OscillatorNode Source # | |
Read OscillatorNode Source # | |
Show OscillatorNode Source # | |
JSArg OscillatorNode Source # | |
AudioNode OscillatorNode Source # | Instantizes OscillatorNode with the default values |
data OscillatorNodeType Source #
Constructors
GainNode | |
Fields |
data ChannelCountMode :: * where Source #
How channels will be matched between connected inputs and output. Detailed description.
Constructors
Max :: ChannelCountMode | |
ClampedMax :: ChannelCountMode | |
Explicit :: ChannelCountMode |
Procedures
Instantiation functions
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
disconnectDestNode :: AudioNode a => a -> a -> WebAudio () Source #
disconnectDestParam :: AudioNode a => a -> AudioParam -> WebAudio () Source #
disconnectDestParamSpec :: AudioNode a => a -> AudioParam -> Int -> WebAudio () Source #
Change AudioParam
value
Different functions for altering the values of AudioParam
s (immediately, ramping, etc.)
setValueAtTime :: AudioParam -> Double -> Double -> WebAudio () Source #
linearRampToValueAtTime :: AudioParam -> Double -> Double -> WebAudio () Source #
exponentialRampToValueAtTime :: AudioParam -> Double -> Double -> WebAudio () Source #
setTargetAtTime :: AudioParam -> Double -> Double -> Double -> WebAudio () Source #
cancelScheduledValues :: AudioParam -> Double -> WebAudio () Source #