csound-expression-5.4.3: library to make electronic music
Safe HaskellNone
LanguageHaskell2010

Csound.Air.Granular

Description

The Csound contains a set of functions for granular synthesis. Unfortunately they are very hard to use due to large number of arguments. This module attempts to set most of the arguments with sensible defaults. So that a novice could start to use it. The defaults are implemented with the help of the class Default. It's a standard way to implement defaults in the Haskell. The class Defaults defines a single constnat called def. With def we can get the default value for the given type.

Several csound opcodes are reimplemented so that first argument contains secondary parameters. The type for parameters always has the instance for the class Default. The original csound opcodes are defined in the end of the module with prefix csd.

Also many granular synth opcodes expect the sound file as input. There are predefined versions of the opcodes that take in the file names instead of tables with sampled sound. They have suffix Snd for stereo and Snd1 for mono files.

For example, that's how we can use the granule opcode:

dac $ granuleSnd1 spec [1, 2, 3] grainSize "fox.wav"

No need to set all 22 parameters. Look at the official tutorial (on github) for more examples.

The five functions are reimplemented in this way: sndwarp, syncgrain, partikkel, granule, fof2.

The most often used arguments are:

  • Scale factors for tempo and pitch: TempoSig or speed and PitchSig. Ranges in 0 to 1
  • Grain size is the size of produced grains in seconds. Good range is 0.005 to 0.01 or even 0.1. The higer the value the more it sounds like the original sound.
  • Grain rate. It's the speed of grain production in Hz. If it's in audio range we can no longer percieve the original pitch of the file. Then the pitch is determined with grain rate value.
  • Grain gap. It's the gap in samples between the grains. Good values are 1 to 100.
  • Grain window function. For the sound to be a grain it have to be enveloped with grain window (some sort of bell shaped envelope). We can use half-sine for this purpose (and it's so in most of the defauts) or we can use a table in the GEN20 family. In the library they implemented as window tables see the table constructors with prefix win.

Usual order of arguments is: GrainRate, GrainSize, TempoSig, PitchSig, file table or name, poniter to the table.

Synopsis

Documentation

Grainy (simple partikkel)

data RndGrainySpec Source #

Randomized parameters for function grainy. We can randomize pitch scaleing factor (0 to 1), read position (in ratio: 0 to 1), and duration of the grains (in seconds, in magnitude of 0.005 to 0.5).

Instances

Instances details
Default RndGrainySpec Source # 
Instance details

Defined in Csound.Air.Granular

Methods

def :: RndGrainySpec #

grainy :: GrainRate -> GrainSize -> TempoSig -> PitchSig -> String -> Sig2 Source #

Simplified version of partikkel. The partikkel for stereo sounds.

grainy1 speed grainrate grainsize kfreqFactor file
  • speed - speed of the playback
  • grainrate - rate of the grain creation
  • grainsize - size of the grains
  • file - filename of an audio file to read the grains.

grainy1 :: GrainRate -> GrainSize -> TempoSig -> PitchSig -> String -> Sig Source #

Simplified version of partikkel. The partikkel for mono sounds.

grainy1 speed grainrate grainsize kfreqFactor file
  • speed - speed of the playback
  • grainrate - rate of the grain creation
  • grainsize - size of the grains
  • file - filename of an audio file to read the grains.

rndGrainy :: RndGrainySpec -> GrainRate -> GrainSize -> TempoSig -> PitchSig -> String -> SE Sig2 Source #

Randomized version of grainy.

rndGrainy1 :: RndGrainySpec -> GrainRate -> GrainSize -> TempoSig -> PitchSig -> String -> SE Sig Source #

Randomized version of grainy1.

ptrGrainy :: GrainRate -> GrainSize -> PitchSig -> Tab -> Pointer -> Sig Source #

Simplified version of partikkel with pointer access to the table. The partikkel for mono sounds.

ptrGrainy grainrate grainsize kfreqFactor tab apnter
  • speed - speed of the playback
  • grainrate - rate of the grain creation
  • grainsize - size of the grains
  • tab - table with sampled sound.
  • apnter - pointer to the table. pointer is relative to total size (0 to 1).

rndPtrGrainy :: RndGrainySpec -> GrainRate -> GrainSize -> PitchSig -> Tab -> Pointer -> SE Sig Source #

Randomized version of ptrGrainy.

ptrGrainySnd :: GrainRate -> GrainSize -> PitchSig -> String -> Pointer -> Sig2 Source #

Simplified version of partikkel with pointer access to the table. The partikkel for mono sounds.

ptrGrainy grainrate grainsize kfreqFactor tab apnter
  • speed - speed of the playback
  • grainrate - rate of the grain creation
  • grainsize - size of the grains
  • file - file with sampled sound.
  • apnter - pointer to the table in seconds

ptrGrainySnd1 :: GrainRate -> GrainSize -> PitchSig -> String -> Pointer -> Sig Source #

Simplified version of partikkel with pointer access to the table. The partikkel for mono sounds.

ptrGrainy grainrate grainsize kfreqFactor tab apnter
  • speed - speed of the playback
  • grainrate - rate of the grain creation
  • grainsize - size of the grains
  • file - file with sampled sound.
  • apnter - pointer to the table in seconds

Sndwarp

data SndwarpSpec Source #

Sndwarp secondary parameters. It's instance of Default, we can use the constant def to get the value.

  • WinSize - window size in seconds (not in samples as in Csound!). The default is 0.1
  • Randw - the bandwidth of a random number generator. The random numbers will be added to iwsize. It's measured in ratio to WinSize. So the 1 means the one WinSize length. The default is 0.3
  • Overlap - determines the density of overlapping windows. The default value is 50. It's in range (0 to 100)

Instances

Instances details
Default SndwarpSpec Source # 
Instance details

Defined in Csound.Air.Granular

Methods

def :: SndwarpSpec #

sndwarp :: SndwarpSpec -> TempoSig -> PitchSig -> Tab -> Sig Source #

Simple sndwarp with scaling mode (corresponds to Csound's initmode == 0).

sndwarp spec resample speed ftab
  • spec - secondary params (use def to get the defaults)
  • resample - the factor by which to change the pitch of the sound. For example, a value of 2 will produce a sound one octave higher than the original. The timing of the sound, however, will not be altered.
  • speed - the factor by which to change the tempo of the sound.
  • ftab -- table with the samples

sndwarpst :: SndwarpSpec -> TempoSig -> PitchSig -> Tab -> Sig2 Source #

Stereo version of the sndwarp.

sndwarpSnd :: SndwarpSpec -> TempoSig -> PitchSig -> String -> Sig2 Source #

Sndwarp that is defined on stereo audio files. We provide the filename instead of table. The rest is the same.

sndwarpSnd1 :: SndwarpSpec -> TempoSig -> PitchSig -> String -> Sig Source #

Sndwarp that is defined on mono audio files. We provide the filename instead of table. The rest is the same.

ptrSndwarp :: SndwarpSpec -> PitchSig -> Tab -> Pointer -> Sig Source #

The simple sndwarp with pointer (Csound initmode = 1).

sndwarp spec resample ftab ptr
  • spec - secondary params (use def to get the defaults)
  • resample - the factor by which to change the pitch of the sound. For example, a value of 2 will produce a sound one octave higher than the original. The timing of the sound, however, will not be altered.
  • ftab -- table with the samples
  • ptr - pointer to read the table (in seconds).

ptrSndwarpst :: SndwarpSpec -> PitchSig -> Tab -> Pointer -> Sig2 Source #

Stereo version of ptrSndwarp.

ptrSndwarpSnd :: SndwarpSpec -> PitchSig -> String -> Pointer -> Sig2 Source #

ptrSndwarp that is defined on stereo audio files. We provide the filename instead of table. The rest is the same.

ptrSndwarpSnd1 :: SndwarpSpec -> PitchSig -> String -> Pointer -> Sig Source #

ptrSndwarp that is defined on mono audio files. We provide the filename instead of table. The rest is the same.

Syncgrain

data SyncgrainSpec Source #

Secondary parameters for syncgrain.

  • Win -- grain window function (half-sine is used by default)
  • Overlap -- grain overlap (use values in range 0 to 100, the 25 is default)

Constructors

SyncgrainSpec 

Instances

Instances details
Default SyncgrainSpec Source # 
Instance details

Defined in Csound.Air.Granular

Methods

def :: SyncgrainSpec #

data RndSyncgrainSpec Source #

Randomized parameters for arguments (in range 0 to 1).

Instances

Instances details
Default RndSyncgrainSpec Source # 
Instance details

Defined in Csound.Air.Granular

syncgrain :: SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> Tab -> Sig Source #

Synchronous granular synthesis.

syncgrain implements synchronous granular synthesis. The source sound for the grains is obtained by reading a function table containing the samples of the source waveform. For sampled-sound sources, GEN01 is used. syncgrain will accept deferred allocation tables.

syncgrain spec graidDuration timeScale PitchSig ftab
  • spec - secondary params (use def to get the defaults)
  • graidDuration - duration of grains in seconds.
  • timeScale - tempo scaling factor.
  • PitchSig - pitch scaling factor.
  • ftab - table with sampled sound.

syncgrainSnd :: SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> String -> Sig2 Source #

syncgrain that is defined on stereo audio files. We provide the filename instead of table. The rest is the same.

syncgrainSnd1 :: SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> String -> Sig Source #

syncgrain that is defined on mono audio files. We provide the filename instead of table. The rest is the same.

rndSyncgrain :: RndSyncgrainSpec -> SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> Tab -> SE Sig Source #

The syncgrain with randomized parameters.

rndSyncgrainSnd :: RndSyncgrainSpec -> SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> String -> SE Sig2 Source #

rndSyncgrain that is defined on stereo audio files. We provide the filename instead of table. The rest is the same.

rndSyncgrainSnd1 :: RndSyncgrainSpec -> SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> String -> SE Sig Source #

rndSyncgrain that is defined on mono audio files. We provide the filename instead of table. The rest is the same.

Granule

data GranuleSpec Source #

Secondary parameters for granule. We can use the def to get the defaults.

  • Gap - gap between grains in sec.
  • Voice - number of voices (integer value in magnitude of 1 to 128, 64 is default)
  • Ratio - ratio of the speed of the gskip pointer relative to output audio sample rate (the default is 1)
  • Mode - playback mode (see GranuleMode, play forward is the default)
  • Skip_os - gskip pointer random offset in sec, 0 will be no offset (0.5 is default).
  • Gap_os - gap random offset in ratios (0 to 1) of the gap size, 0 gives no offset (0.5 is default).
  • Size_os -grain size random offset in ratios (0 to 1) of grain size, 0 gives no offset (0.5 is default).
  • Seed - seed for the random number generator (0.5 is default).
  • Att - attack of the grain envelope in ratios (0 to 1) of grain size (0.3 is default).
  • Dec - decay of the grain envelope in ratios (0 to 1) of grain size (0.3 is default).

Instances

Instances details
Default GranuleSpec Source # 
Instance details

Defined in Csound.Air.Granular

Methods

def :: GranuleSpec #

data GranuleMode Source #

Granule playback mode.

Instances

Instances details
Default GranuleMode Source # 
Instance details

Defined in Csound.Air.Granular

Methods

def :: GranuleMode #

granule :: GranuleSpec -> [ConstPitchSig] -> GrainSize -> Tab -> Sig Source #

A more complex granular synthesis texture generator.

granule is a Csound unit generator which employs a wavetable as input to produce granularly synthesized audio output. Wavetable data may be generated by any of the GEN subroutines such as GEN01 which reads an audio data file into a wavetable. This enable a sampled sound to be used as the source for the grains. Up to 128 voices are implemented internally. The maximum number of voices can be increased by redefining the variable MAXVOICE in the grain4.h file. granule has a build-in random number generator to handle all the random offset parameters. Thresholding is also implemented to scan the source function table at initialization stage. This facilitates features such as skipping silence passage between sentences.

granule spec chord grainSize ftab
  • spec -- secondary parameters. We can use def to get the defaults.
  • chord :: [D] -- the list of pitch factors to scale the original sound. It can be up to 4 items long. This parameters allows us to create a chords out of grains.
  • grainSize -- grain size in sec.
  • ftab - table with sampled sound.

granuleSnd :: GranuleSpec -> [ConstPitchSig] -> GrainSize -> String -> Sig2 Source #

granule that is defined on stereo audio files. We provide the filename instead of table. The rest is the same.

granuleSnd1 :: GranuleSpec -> [ConstPitchSig] -> GrainSize -> String -> Sig Source #

granule that is defined on mono audio files. We provide the filename instead of table. The rest is the same.

Partikkel

partikkel :: PartikkelSpec -> GrainRate -> GrainSize -> PitchSig -> [Tab] -> [Pointer] -> Sig Source #

Granular synthesizer with "per grain" control over many of its parameters. Has a sync input to sychronize its internal grain scheduler clock to an external clock source.

partikkel was conceived after reading Curtis Roads' book Microsound, and the goal was to create an opcode that was capable of all time-domain varieties of granular synthesis described in this book. The idea being that most of the techniques only differ in parameter values, and by having a single opcode that can do all varieties of granular synthesis makes it possible to interpolate between techniques. Granular synthesis is sometimes dubbed particle synthesis, and it was thought apt to name the opcode partikkel to distinguish it from other granular opcodes.

partikkel spec grainrate grainsize kpitch ifiltabs apnters
  • spec - secondary parameters
  • grainrate - rate of the grain creation
  • grainsize - grain size in sec (!!!not in ms as for Csound!!!).
  • kpitch -- pitch scaling factor.
  • apnters -- list of pointers (up to 4 values can be used)
  • ifiltabs -- list of tables (up to 4 values can be used)

Fof2

data Fof2Spec Source #

Defaults for fof2 opcode.

Instances

Instances details
Default Fof2Spec Source # 
Instance details

Defined in Csound.Air.Granular

Methods

def :: Fof2Spec #

fof2 :: Fof2Spec -> GrainRate -> GrainSize -> Tab -> Pointer -> Sig Source #

Reimplementation of fof2 opcode.

fof2Snd :: Fof2Spec -> GrainRate -> GrainSize -> TempoSig -> String -> Sig2 Source #

Reimplementation of fof2 opcode for stereo audio files.

fof2Snd1 :: Fof2Spec -> GrainRate -> GrainSize -> TempoSig -> String -> Sig Source #

Reimplementation of fof2 opcode for mono audio files.

Granular delays

This block is for granular delay effects. To make granular delay from the granular functions it has to support reading from table with pointer (phasor). All functions have the same four parameters:

  • maxDelayTime -- maximum delay length in seсoncds.
  • delayTime -- delay time (it can vary. it's a signal).
  • feedback -- amount of feedback. How much of processed signal is mixed to the delayed signal
  • balance -- mix between dry and wet signal. 0 is dry only signal. 1 is wet only signl.

The rest arguments are taken from the original granular functions.

grainyDelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> GrainRate -> GrainSize -> PitchSig -> Sig -> SE Sig Source #

Granular delay effect for grainy.

rndGrainyDelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> RndGrainySpec -> GrainRate -> GrainSize -> PitchSig -> Sig -> SE Sig Source #

Granular delay effect for rndGrainy.

sndwarpDelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> SndwarpSpec -> PitchSig -> Sig -> SE Sig Source #

Granular delay effect for sndwarp.

syncgrainDelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> Sig -> SE Sig Source #

Granular delay effect for syncgrain.

rndSyncgrainDelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> RndSyncgrainSpec -> SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> Sig -> SE Sig Source #

Granular delay effect for rndSyncgrain.

partikkelDelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> PartikkelSpec -> GrainRate -> GrainSize -> PitchSig -> Sig -> SE Sig Source #

Granular delay effect for partikkel.

fofDelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> Fof2Spec -> GrainRate -> GrainSize -> Sig -> SE Sig Source #

Granular delay effect for fof2. Good values for grain rate and size are

grainRate = 25
grainSize = 2.5

Granular effets

The functions are based on the granular delays. each function is a granular delay with zero feedback and instant delay time.

grainyFx :: GrainRate -> GrainSize -> PitchSig -> Sig -> SE Sig Source #

Granular effect for grainy.

rndGrainyFx :: RndGrainySpec -> GrainRate -> GrainSize -> PitchSig -> Sig -> SE Sig Source #

Granular effect for rndGrainy.

sndwarpFx :: SndwarpSpec -> PitchSig -> Sig -> SE Sig Source #

Granular effect for sndwarp.

syncgrainFx :: SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> Sig -> SE Sig Source #

Granular effect for syncgrain.

rndSyncgrainFx :: RndSyncgrainSpec -> SyncgrainSpec -> GrainSize -> TempoSig -> PitchSig -> Sig -> SE Sig Source #

Granular effect for rndSyncgrain.

partikkelFx :: PartikkelSpec -> GrainRate -> GrainSize -> PitchSig -> Sig -> SE Sig Source #

Granular effect for partikkel.

fofFx :: Fof2Spec -> GrainRate -> GrainSize -> Sig -> SE Sig Source #

Granular effect for fof2.

Csound functions

csdSndwarp :: Sig -> Sig -> Sig -> Tab -> D -> D -> D -> D -> Tab -> D -> Sig Source #

Reads a mono sound sample from a table and applies time-stretching and/or pitch modification.

sndwarp reads sound samples from a table and applies time-stretching and/or pitch modification. Time and frequency modification are independent from one another. For example, a sound can be stretched in time while raising the pitch!

ares [, ac]  sndwarp  xamp, xtimewarp, xresample, ifn1, ibeg, iwsize, \
          irandw, ioverlap, ifn2, itimemode

csound doc: http://www.csounds.com/manual/html/sndwarp.html

csdSndwarpst :: Sig -> Sig -> Sig -> Tab -> D -> D -> D -> D -> Tab -> D -> Sig2 Source #

Reads a stereo sound sample from a table and applies time-stretching and/or pitch modification.

sndwarpst reads stereo sound samples from a table and applies time-stretching and/or pitch modification. Time and frequency modification are independent from one another. For example, a sound can be stretched in time while raising the pitch!

ar1, ar2 [,ac1] [, ac2]  sndwarpst  xamp, xtimewarp, xresample, ifn1, \
          ibeg, iwsize, irandw, ioverlap, ifn2, itimemode

csound doc: http://www.csounds.com/manual/html/sndwarpst.html

csdSyncgrain :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> D -> Sig Source #

Synchronous granular synthesis.

syncgrain implements synchronous granular synthesis. The source sound for the grains is obtained by reading a function table containing the samples of the source waveform. For sampled-sound sources, GEN01 is used. syncgrain will accept deferred allocation tables.

asig  syncgrain  kamp, kfreq, kpitch, kgrsize, kprate, ifun1, \
          ifun2, iolaps

csound doc: http://www.csounds.com/manual/html/syncgrain.html

csdGranule :: Sig -> D -> D -> D -> D -> Tab -> D -> D -> D -> D -> Sig -> D -> Sig -> D -> D -> D -> Sig Source #

A more complex granular synthesis texture generator.

The granule unit generator is more complex than grain, but does add new possibilities.

ares  granule  xamp, ivoice, iratio, imode, ithd, ifn, ipshift, igskip, \
          igskip_os, ilength, kgap, igap_os, kgsize, igsize_os, iatt, idec \
          [, iseed] [, ipitch1] [, ipitch2] [, ipitch3] [, ipitch4] [, ifnenv]

csound doc: http://www.csounds.com/manual/html/granule.html

csdPartikkel :: Tuple a => Sig -> Sig -> Tab -> Sig -> Sig -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig -> Sig -> Tab -> Tab -> Sig -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Tab -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> a Source #

Granular synthesizer with "per grain" control over many of its parameters. Has a sync input to sychronize its internal grain scheduler clock to an external clock source.

partikkel was conceived after reading Curtis Roads' book Microsound, and the goal was to create an opcode that was capable of all time-domain varieties of granular synthesis described in this book. The idea being that most of the techniques only differ in parameter values, and by having a single opcode that can do all varieties of granular synthesis makes it possible to interpolate between techniques. Granular synthesis is sometimes dubbed particle synthesis, and it was thought apt to name the opcode partikkel to distinguish it from other granular opcodes.

a1 [, a2, a3, a4, a5, a6, a7, a8]  partikkel  agrainfreq, \
                  kdistribution, idisttab, async, kenv2amt, ienv2tab, ienv_attack, \
                  ienv_decay, ksustain_amount, ka_d_ratio, kduration, kamp, igainmasks, \
                  kwavfreq, ksweepshape, iwavfreqstarttab, iwavfreqendtab, awavfm, \
                  ifmamptab, kfmenv, icosine, ktraincps, knumpartials, kchroma, \
                  ichannelmasks, krandommask, kwaveform1, kwaveform2, kwaveform3, \
                  kwaveform4, iwaveamptab, asamplepos1, asamplepos2, asamplepos3, \
                  asamplepos4, kwavekey1, kwavekey2, kwavekey3, kwavekey4, imax_grains \
                  [, iopcode_id]

csound doc: http://www.csounds.com/manual/html/partikkel.html