csound-sampler-0.0.8.0: A musical sampler based on Csound

Safe HaskellNone
LanguageHaskell98

Csound.Sam

Contents

Description

The sampler

Synopsis

Documentation

data Sample a Source #

The generic type for samples.

Instances

Functor Sample Source # 

Methods

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

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

Applicative Sample Source # 

Methods

pure :: a -> Sample a #

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

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

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

RenderCsd Sam Source # 

Methods

renderCsdBy :: Options -> Sam -> IO String #

Fractional a => Fractional (Sample a) Source # 

Methods

(/) :: Sample a -> Sample a -> Sample a #

recip :: Sample a -> Sample a #

fromRational :: Rational -> Sample a #

Num a => Num (Sample a) Source # 

Methods

(+) :: Sample a -> Sample a -> Sample a #

(-) :: Sample a -> Sample a -> Sample a #

(*) :: Sample a -> Sample a -> Sample a #

negate :: Sample a -> Sample a #

abs :: Sample a -> Sample a #

signum :: Sample a -> Sample a #

fromInteger :: Integer -> Sample a #

RenderCsd (Source Sam) Source # 
SigSpace a => SigSpace (Sample a) Source # 

Methods

mapSig :: (Sig -> Sig) -> Sample a -> Sample a #

type DurOf Sam # 
type DurOf Sam = D
type AtOut Sig2 Sig2 Sam # 
type AtOut Sig Sig2 Sam # 
type AtOut Sig2 (SE Sig2) Sam # 
type AtOut Sig2 (SE Sig2) Sam = Sam
type AtOut Sig (SE Sig2) Sam # 
type AtOut Sig (SE Sig2) Sam = Sam
type AtOut Sig (SE Sig) Sam # 
type AtOut Sig (SE Sig) Sam = Sam

type Sam = Sample Sig2 Source #

The main type. A stereo sample.

type Bpm = D Source #

The Beats Per Minute measure (BPM). Almost all values are measured in BPMs.

Lifters

mapBpm :: (Bpm -> a -> b) -> Sample a -> Sample b Source #

Transforms the sample with BPM.

bindSam :: (a -> SE b) -> Sample a -> Sample b Source #

Lifts bind on stereo signals to samples.

bindBpm :: (Bpm -> a -> SE b) -> Sample a -> Sample b Source #

Lifts bind on stereo signals to samples with BPM.

liftSam :: Sample (SE a) -> Sample a Source #

Hides the effects inside sample.

mapBpm2 :: (Bpm -> a -> b -> c) -> Sample a -> Sample b -> Sample c Source #

Transforms the sample with BPM.

bindBpm2 :: (Bpm -> a -> b -> SE c) -> Sample a -> Sample b -> Sample c Source #

Lifts bind on stereo signals to samples with BPM.

withBpm :: (Bpm -> Sample a) -> Sample a Source #

Constructors

sig1 :: D -> Sig -> Sam Source #

Constructs sample from limited mono signal (duration is in seconds)

sig2 :: D -> Sig2 -> Sam Source #

Constructs sample from limited stereo signal (duration is in seconds)

infSig1 :: Sig -> Sam Source #

Constructs sample from mono signal

infSig2 :: Sig2 -> Sam Source #

Constructs sample from stereo signal

fromSig1 :: D -> Sig -> Sam Source #

Constructs sample from limited mono signal (duration is in BPMs)

fromSig2 :: D -> Sig2 -> Sam Source #

Constructs sample from limited stereo signal (duration is in BPMs)

class ToSam a where Source #

Minimal complete definition

toSam

Methods

toSam :: a -> Sam Source #

Instances

ToSam Sig2 Source # 

Methods

toSam :: Sig2 -> Sam Source #

ToSam Sig Source # 

Methods

toSam :: Sig -> Sam Source #

ToSam (SE Sig2) Source # 

Methods

toSam :: SE Sig2 -> Sam Source #

ToSam (SE Sig) Source # 

Methods

toSam :: SE Sig -> Sam Source #

limSam :: ToSam a => D -> a -> Sam Source #

Stereo

wav :: String -> Sam Source #

Constructs sample from wav or aiff files.

wavr :: String -> Sam Source #

Constructs sample from wav that is played in reverse.

seg :: D -> D -> String -> Sam Source #

Constructs sample from the segment of a wav file. The start and end times are measured in seconds.

seg begin end fileName

segr :: D -> D -> String -> Sam Source #

rndWav :: D -> String -> Sam Source #

Picks segments from the wav file at random. The first argument is the length of the segment.

rndWavr :: D -> String -> Sam Source #

Picks segments from the wav file at random. The first argument is the length of the segment.

rndSeg :: D -> D -> D -> String -> Sam Source #

Constructs random segments of the given length from an interval.

rndSegr :: D -> D -> D -> String -> Sam Source #

Constructs reversed random segments of the given length from an interval.

ramWav :: LoopMode -> Sig -> String -> Sam Source #

Reads a sample from the file in RAM.

ramWav loopMode speed fileName

Mono

wav1 :: String -> Sam Source #

Constructs sample from mono wav or aiff files.

wavr1 :: String -> Sam Source #

Constructs sample from mono wav that is played in reverse.

seg1 :: D -> D -> String -> Sam Source #

Constructs sample from the segment of a mono wav file. The start and end times are measured in seconds.

seg begin end fileName

segr1 :: D -> D -> String -> Sam Source #

rndWav1 :: D -> String -> Sam Source #

Picks segments from the mono wav file at random. The first argument is the length of the segment.

rndWavr1 :: D -> String -> Sam Source #

Picks segments from the mono wav file at random. The first argument is the length of the segment.

rndSeg1 :: D -> D -> D -> String -> Sam Source #

Constructs random segments of the given length from an interval.

rndSegr1 :: D -> D -> D -> String -> Sam Source #

Constructs reversed random segments of the given length from an interval.

ramWav1 :: LoopMode -> Sig -> String -> Sam Source #

Reads a sample from the mono file in RAM.

ramWav1 loopMode speed fileName

Reading from RAM

Stereo

ramLoop :: Fidelity -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as loopRam but wrapped in Sam (see Csound.Air.Wav).

ramRead :: Fidelity -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as readRam but wrapped in Sam (see Csound.Air.Wav).

segLoop :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as loopSeg but wrapped in Sam (see Csound.Air.Wav).

segRead :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as readSeg but wrapped in Sam (see Csound.Air.Wav).

relLoop :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as loopRel but wrapped in Sam (see Csound.Air.Wav).

relRead :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as readRel but wrapped in Sam (see Csound.Air.Wav).

Mono

ramLoop1 :: Fidelity -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as loopRam1 but wrapped in Sam (see Csound.Air.Wav).

ramRead1 :: Fidelity -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as readRam1 but wrapped in Sam (see Csound.Air.Wav).

segLoop1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as loopSeg1 but wrapped in Sam (see Csound.Air.Wav).

segRead1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as readSeg1 but wrapped in Sam (see Csound.Air.Wav).

relLoop1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as loopRel1 but wrapped in Sam (see Csound.Air.Wav).

relRead1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam Source #

It's the same as readRel1 but wrapped in Sam (see Csound.Air.Wav).

Tempo/pitch scaling based on temposcal

Envelopes

linEnv :: D -> D -> Sam -> Sam Source #

A linear rise-decay envelope. Times a given in BPMs.

linEnv rise dec sample

expEnv :: D -> D -> Sam -> Sam Source #

An exponential rise-decay envelope. Times a given in BPMs.

expEnv rise dec sample

hatEnv :: Sam -> Sam Source #

Parabolic envelope that starts and ends at zero and reaches maximum at the center.

decEnv :: Sam -> Sam Source #

Fade out linear envelope.

riseEnv :: Sam -> Sam Source #

Fade in linear envelope.

edecEnv :: Sam -> Sam Source #

Fade out exponential envelope.

eriseEnv :: Sam -> Sam Source #

Fade in exponential envelope.

Arrange

wide :: D -> Sam -> Sam Source #

Makes the sampler broader. It's reciprocal of str

wide k = str (1 / k)

flow :: [Sam] -> Sam Source #

Plays a list of samples one after another.

pick :: Sig -> [Sam] -> Sam Source #

Picks samples at random. The first argument is the period ofmetronome in BPMs. The tick of metronome produces new random sample from the list.

pickBy :: Sig -> [(Sig, Sam)] -> Sam Source #

Picks samples at random. We can specify a frequency of the occurernce. The sum of all frequencies should be equal to 1.

atPan :: Sig -> Sam -> Sam Source #

Panning. 0 is all left and 1 is all right.

atPch :: Sig -> Sam -> Sam Source #

Scales sample by pitch in tones.

atCps :: Sig -> Sam -> Sam Source #

Scales sample by pitch in factor of frequency.

atPanRnd :: Sam -> Sam Source #

Applies random panning to every sample playback.

atVolRnd :: (D, D) -> Sam -> Sam Source #

Applies random amplitude scaling to every sample playback.

atVolGauss :: D -> Sam -> Sam Source #

Applies random amplitude scaling with gauss distribution with given radius (centered at 1).

Loops

rep1 :: D -> Sam -> Sam Source #

Plays the sample at the given period (in BPMs). The samples don't overlap.

rep :: [D] -> Sam -> Sam Source #

Plays the sample at the given pattern of periods (in BPMs). The samples don't overlap.

pat1 :: D -> Sam -> Sam Source #

Plays the sample at the given period (in BPMs). The overlapped samples are mixed together.

pat :: [D] -> Sam -> Sam Source #

Plays the sample at the given pattern of periods (in BPMs). The overlapped samples are mixed together.

pat' :: [D] -> [D] -> Sam -> Sam Source #

Plays the sample at the given pattern of volumes and periods (in BPMs). The overlapped samples are mixed together.

pat' volumes periods

rndPat :: Sig -> [D] -> Sam -> Sam Source #

Plays the sample at the given pattern of periods (in BPMs) and sometimes skips the samples from playback. The overlapped samples are mixed together. The first argument is the probability of inclusion.

rndPat' :: Sig -> [D] -> [D] -> Sam -> Sam Source #

Plays the sample at the given pattern of volumes and periods (in BPMs) and sometimes skips the samples from playback. The overlapped samples are mixed together. The first argument is the probability of inclusion.

rndPat' probability volumes periods

Arpeggio

type Chord = [D] Source #

The tones of the chord.

arpUp :: Chord -> [D] -> Sam -> Sam Source #

Plays ascending arpeggio of samples.

arpDown :: Chord -> [D] -> Sam -> Sam Source #

Plays descending arpeggio of samples.

arpOneOf :: Chord -> [D] -> Sam -> Sam Source #

Plays arpeggio of samles with random notes from the chord.

arpFreqOf :: [Sig] -> Chord -> [D] -> Sam -> Sam Source #

Plays arpeggio of samles with random notes from the chord. We can assign the frequencies of the notes.

arpUp1 :: Chord -> Sig -> Sam -> Sam Source #

Plays ascending arpeggio of samples.

arpDown1 :: Chord -> Sig -> Sam -> Sam Source #

Plays descending arpeggio of samples.

arpOneOf1 :: Chord -> Sig -> Sam -> Sam Source #

Plays arpeggio of samles with random notes from the chord.

arpFreqOf1 :: [Sig] -> Chord -> Sig -> Sam -> Sam Source #

Plays arpeggio of samles with random notes from the chord. We can assign the frequencies of the notes.

Misc patterns

wall :: D -> Sam -> Sam Source #

Constructs the wall of sound from the initial segment of the sample. The segment length is given in BPMs.

wall segLength

forAirports :: [(D, D, D)] -> Sam -> Sam Source #

The pattern is influenced by the Brian Eno's work "Music fo Airports". The argument is list of tripples:

(delayTime, repeatPeriod, pitch)

It takes a Sample and plays it in the loop with given initial delay time. The third cell in the tuple pitch is a value for scaling of the pitch in tones.

genForAirports :: [(D, D, Sam)] -> Sam Source #

The pattern is influenced by the Brian Eno's work "Music fo Airports". It's more generic than pattern forAirport The argument is list of tripples:

(delayTime, repeatPeriod, Sample)

It takes a list of Samples and plays them in the loop with given initial delay time and repeat period.

arpy :: (D -> SE Sig2) -> D -> D -> Int -> [[D]] -> Sam Source #

The arpeggiator for the sequence of chords.

arpy instrument chordPeriod speedOfTheNote accentNumber chords 

The first argument is an instrument that takes in a frequency of the note in Hz. The second argument is the period of chord change (in beats). The next argument is the speed of the single note (in beats). The integer argument is number of notes in the group. Every n'th note is louder. The last argument is the sequence of chords. The chord is the list of frequencies.

Utils

toSec :: Bpm -> D -> D Source #

UIs

Triggering samples

Orphan instances

Loop Sam Source # 

Methods

loop :: Sam -> Sam #

Limit Sam Source # 

Methods

lim :: DurOf Sam -> Sam -> Sam #

Rest Sam Source # 

Methods

rest :: DurOf Sam -> Sam #

Stretch Sam Source # 

Methods

str :: DurOf Sam -> Sam -> Sam #

Delay Sam Source # 

Methods

del :: DurOf Sam -> Sam -> Sam #

Compose Sam Source # 
Harmony Sam Source # 

Methods

har :: [Sam] -> Sam #

(=:=) :: Sam -> Sam -> Sam #

Melody Sam Source # 

Methods

mel :: [Sam] -> Sam #

(+:+) :: Sam -> Sam -> Sam #

MixAt Sig2 Sig2 Sam Source # 

Methods

mixAt :: Sig -> (Sig2 -> Sig2) -> Sam -> AtOut Sig2 Sig2 Sam #

MixAt Sig Sig2 Sam Source # 

Methods

mixAt :: Sig -> (Sig -> Sig2) -> Sam -> AtOut Sig Sig2 Sam #

At Sig2 Sig2 Sam Source # 

Associated Types

type AtOut Sig2 Sig2 Sam :: * #

Methods

at :: (Sig2 -> Sig2) -> Sam -> AtOut Sig2 Sig2 Sam #

At Sig Sig2 Sam Source # 

Associated Types

type AtOut Sig Sig2 Sam :: * #

Methods

at :: (Sig -> Sig2) -> Sam -> AtOut Sig Sig2 Sam #

MixAt Sig2 (SE Sig2) Sam Source # 

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> Sam -> AtOut Sig2 (SE Sig2) Sam #

MixAt Sig (SE Sig2) Sam Source # 

Methods

mixAt :: Sig -> (Sig -> SE Sig2) -> Sam -> AtOut Sig (SE Sig2) Sam #

MixAt Sig (SE Sig) Sam Source # 

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sam -> AtOut Sig (SE Sig) Sam #

At Sig2 (SE Sig2) Sam Source # 

Associated Types

type AtOut Sig2 (SE Sig2) Sam :: * #

Methods

at :: (Sig2 -> SE Sig2) -> Sam -> AtOut Sig2 (SE Sig2) Sam #

At Sig (SE Sig2) Sam Source # 

Associated Types

type AtOut Sig (SE Sig2) Sam :: * #

Methods

at :: (Sig -> SE Sig2) -> Sam -> AtOut Sig (SE Sig2) Sam #

At Sig (SE Sig) Sam Source # 

Associated Types

type AtOut Sig (SE Sig) Sam :: * #

Methods

at :: (Sig -> SE Sig) -> Sam -> AtOut Sig (SE Sig) Sam #