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

Safe HaskellNone

Csound.Sam

Contents

Description

The sampler

Synopsis

Documentation

data Sample a Source

The generic type for samples.

Instances

Functor Sample 
Applicative Sample 
RenderCsd Sam 
Fractional a => Fractional (Sample a) 
Num a => Num (Sample a) 
SigSpace a => SigSpace (Sample a) 

type Sam = Sample Sig2Source

The main type. A stereo sample.

type Bpm = DSource

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

runSam :: Bpm -> Sam -> SE Sig2Source

Lifters

mapBpm :: (Bpm -> Sig2 -> Sig2) -> Sam -> SamSource

Transforms the sample with BPM.

bindSam :: (Sig2 -> SE Sig2) -> Sam -> SamSource

Lifts bind on stereo signals to samples.

bindBpm :: (Bpm -> Sig2 -> SE Sig2) -> Sam -> SamSource

Lifts bind on stereo signals to samples with BPM.

liftSam :: Sample (SE a) -> Sample aSource

Hides the effects inside sample.

Constructors

sig1 :: D -> Sig -> SamSource

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

sig2 :: D -> Sig2 -> SamSource

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

infSig1 :: Sig -> SamSource

Constructs sample from mono signal

infSig2 :: Sig2 -> SamSource

Constructs sample from stereo signal

fromSig1 :: D -> Sig -> SamSource

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

fromSig2 :: D -> Sig2 -> SamSource

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

rest :: D -> SamSource

Constructs silence. The first argument is length in BPMs.

Stereo

wav :: String -> SamSource

Constructs sample from wav or aiff files.

wavr :: String -> SamSource

Constructs sample from wav that is played in reverse.

seg :: D -> D -> String -> SamSource

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 -> SamSource

rndWav :: D -> String -> SamSource

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

rndWavr :: D -> String -> SamSource

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

rndSeg :: D -> D -> D -> String -> SamSource

Constructs random segments of the given length from an interval.

rndSegr :: D -> D -> D -> String -> SamSource

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

ramWav :: LoopMode -> Sig -> String -> SamSource

Reads a sample from the file in RAM.

 ramWav loopMode speed fileName

Mono

wav1 :: String -> SamSource

Constructs sample from mono wav or aiff files.

wavr1 :: String -> SamSource

Constructs sample from mono wav that is played in reverse.

seg1 :: D -> D -> String -> SamSource

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 -> SamSource

rndWav1 :: D -> String -> SamSource

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

rndWavr1 :: D -> String -> SamSource

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

rndSeg1 :: D -> D -> D -> String -> SamSource

Constructs random segments of the given length from an interval.

rndSegr1 :: D -> D -> D -> String -> SamSource

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

ramWav1 :: LoopMode -> Sig -> String -> SamSource

Reads a sample from the mono file in RAM.

 ramWav1 loopMode speed fileName

Envelopes

linEnv :: D -> D -> Sam -> SamSource

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

 linEnv rise dec sample

expEnv :: D -> D -> Sam -> SamSource

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

 expEnv rise dec sample

hatEnv :: Sam -> SamSource

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

decEnv :: Sam -> SamSource

Fade out linear envelope.

riseEnv :: Sam -> SamSource

Fade in linear envelope.

edecEnv :: Sam -> SamSource

Fade out exponential envelope.

eriseEnv :: Sam -> SamSource

Fade in exponential envelope.

Arrange

del :: D -> Sam -> SamSource

Delays a sample by the given amount of BPMs.

str :: D -> Sam -> SamSource

Stretches the BPM measure.

wide :: D -> Sam -> SamSource

Makes the sampler broader. It's reciprocal of str

 wide k = str (1 / k)

flow :: [Sam] -> SamSource

Plays a list of samples one after another.

pick :: Sig -> [Sam] -> SamSource

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 -> [(D, Sam)] -> SamSource

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

lim :: D -> Sam -> SamSource

Limits the length of the sample. The length is expressed in BPMs.

atPan :: Sig -> Sam -> SamSource

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

atPch :: Sig -> Sam -> SamSource

Scales sample by pitch in tones.

atCps :: Sig -> Sam -> SamSource

Scales sample by pitch in factor of frequency.

Loops

loop :: Sam -> SamSource

Plays sample in the loop.

rep1 :: D -> Sam -> SamSource

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

rep :: [D] -> Sam -> SamSource

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

pat1 :: D -> Sam -> SamSource

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

pat :: [D] -> Sam -> SamSource

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

Arpeggio

type Chord = [D]Source

The tones of the chord.

arpUp :: Chord -> [D] -> Sam -> SamSource

Plays ascending arpeggio of samples.

arpDown :: Chord -> [D] -> Sam -> SamSource

Plays descending arpeggio of samples.

arpOneOf :: Chord -> [D] -> Sam -> SamSource

Plays arpeggio of samles with random notes from the chord.

arpFreqOf :: [D] -> Chord -> [D] -> Sam -> SamSource

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

arpUp1 :: Chord -> Sig -> Sam -> SamSource

Plays ascending arpeggio of samples.

arpDown1 :: Chord -> Sig -> Sam -> SamSource

Plays descending arpeggio of samples.

arpOneOf1 :: Chord -> Sig -> Sam -> SamSource

Plays arpeggio of samles with random notes from the chord.

arpFreqOf1 :: [D] -> Chord -> Sig -> Sam -> SamSource

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

Misc patterns

wall :: D -> Sam -> SamSource

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 -> SamSource

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)] -> SamSource

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.