hsc3-lang-0.14: Haskell SuperCollider Language

Safe HaskellSafe-Inferred

Sound.SC3.Lang.Control.Pitch

Contents

Description

SC3 pitch model implementation.

Synopsis

Pitched

class Pitched p whereSource

Pitched values, minimal definition is midinote.

 midinote (defaultPitch {degree = 5}) == 69
 freq (defaultPitch {degree = 5,detune = 10}) == 440 + 10

Methods

midinote :: p -> DoubleSource

freq :: p -> DoubleSource

Instances

Pitch

data Pitch Source

The supercollider language pitch model is organised as a tree with three separate layers, and is designed to allow separate processes to manipulate aspects of the model independently.

The haskell variant implements Pitch as a labeled data type, with a default value such that scale degree 5 is the A above middle C.

 freq (defaultPitch {degree = 5}) == 440

The note is given as a degree, with a modal transposition, indexing a scale interpreted relative to an equally tempered octave divided into the indicated number of steps.

The midinote is derived from the note by adding the indicated root, octave and gamut transpositions.

The frequency is derived by a chromatic transposition of the midinote, with a harmonic multiplier.

 let {p = defaultPitch
     ;n = p {stepsPerOctave = 12
            ,scale = [0,2,4,5,7,9,11]
            ,degree = 0
            ,mtranspose = 5}
     ;m = n {root = 0
            ,octave = 5
            ,gtranspose = 0}
     ;f = m {ctranspose = 0
            ,harmonic = 1}}
 in (note n,midinote m,freq f) == (9,69,440)

By editing the values of aspects of a pitch, processes can cooperate. Below one process controls the note by editing the modal transposition, a second edits the octave.

 let {edit_mtranspose p d = p {mtranspose = mtranspose p + d}
     ;edit_octave p o = p {octave = octave p + o}
     ;p' = repeat defaultPitch
     ;q = zipWith edit_mtranspose p' [0,2,4,3,5]
     ;r = zipWith edit_octave q [0,-1,0,1,0]
     ;f = map midinote}
 in (f q,f r) == ([60,64,67,65,69],[60,52,67,77,69])

defaultPitch :: PitchSource

A default Pitch value of middle C given as degree 0 of a C major scale.

 let {p = defaultPitch
     ;r = ([0,2,4,5,7,9,11],12,0,5,0)}
 in (scale p,stepsPerOctave p,root p,octave p,degree p) == r

note :: Pitch -> DoubleSource

Calculate note field.

 note (defaultPitch {degree = 5}) == 9

Optional

type T616 a b c = (a, a, a, a, a, a, b, c, c, c, c, c, c)Source

Tuple in 6-1-6 arrangement.

type OptPitch = T616 (Maybe Double) (Maybe [Double]) (Maybe Double)Source

Pitch represented as tuple of optional values.