Safe Haskell | None |
---|---|
Language | Haskell98 |
The sampler
- data Sample a
- type Sam = Sample Sig2
- type Bpm = D
- runSam :: Bpm -> Sam -> SE Sig2
- mapBpm :: (Bpm -> a -> b) -> Sample a -> Sample b
- bindSam :: (a -> SE b) -> Sample a -> Sample b
- bindBpm :: (Bpm -> a -> SE b) -> Sample a -> Sample b
- liftSam :: Sample (SE a) -> Sample a
- mapBpm2 :: (Bpm -> a -> b -> c) -> Sample a -> Sample b -> Sample c
- bindBpm2 :: (Bpm -> a -> b -> SE c) -> Sample a -> Sample b -> Sample c
- withBpm :: (Bpm -> Sample a) -> Sample a
- sig1 :: D -> Sig -> Sam
- sig2 :: D -> Sig2 -> Sam
- infSig1 :: Sig -> Sam
- infSig2 :: Sig2 -> Sam
- fromSig1 :: D -> Sig -> Sam
- fromSig2 :: D -> Sig2 -> Sam
- class ToSam a where
- limSam :: ToSam a => D -> a -> Sam
- wav :: String -> Sam
- wavr :: String -> Sam
- seg :: D -> D -> String -> Sam
- segr :: D -> D -> String -> Sam
- rndWav :: D -> String -> Sam
- rndWavr :: D -> String -> Sam
- rndSeg :: D -> D -> D -> String -> Sam
- rndSegr :: D -> D -> D -> String -> Sam
- ramWav :: LoopMode -> Sig -> String -> Sam
- wav1 :: String -> Sam
- wavr1 :: String -> Sam
- seg1 :: D -> D -> String -> Sam
- segr1 :: D -> D -> String -> Sam
- rndWav1 :: D -> String -> Sam
- rndWavr1 :: D -> String -> Sam
- rndSeg1 :: D -> D -> D -> String -> Sam
- rndSegr1 :: D -> D -> D -> String -> Sam
- ramWav1 :: LoopMode -> Sig -> String -> Sam
- ramLoop :: Fidelity -> TempoSig -> PitchSig -> String -> Sam
- ramRead :: Fidelity -> TempoSig -> PitchSig -> String -> Sam
- segLoop :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- segRead :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- relLoop :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- relRead :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- ramLoop1 :: Fidelity -> TempoSig -> PitchSig -> String -> Sam
- ramRead1 :: Fidelity -> TempoSig -> PitchSig -> String -> Sam
- segLoop1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- segRead1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- relLoop1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- relRead1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sam
- linEnv :: D -> D -> Sam -> Sam
- expEnv :: D -> D -> Sam -> Sam
- hatEnv :: Sam -> Sam
- decEnv :: Sam -> Sam
- riseEnv :: Sam -> Sam
- edecEnv :: Sam -> Sam
- eriseEnv :: Sam -> Sam
- wide :: D -> Sam -> Sam
- flow :: [Sam] -> Sam
- pick :: Sig -> [Sam] -> Sam
- pickBy :: Sig -> [(D, Sam)] -> Sam
- atPan :: Sig -> Sam -> Sam
- atPch :: Sig -> Sam -> Sam
- atCps :: Sig -> Sam -> Sam
- atPanRnd :: Sam -> Sam
- atVolRnd :: (D, D) -> Sam -> Sam
- atVolGauss :: D -> Sam -> Sam
- rep1 :: D -> Sam -> Sam
- rep :: [D] -> Sam -> Sam
- pat1 :: D -> Sam -> Sam
- pat :: [D] -> Sam -> Sam
- pat' :: [D] -> [D] -> Sam -> Sam
- rndPat :: Sig -> [D] -> Sam -> Sam
- rndPat' :: Sig -> [D] -> [D] -> Sam -> Sam
- type Chord = [D]
- arpUp :: Chord -> [D] -> Sam -> Sam
- arpDown :: Chord -> [D] -> Sam -> Sam
- arpOneOf :: Chord -> [D] -> Sam -> Sam
- arpFreqOf :: [D] -> Chord -> [D] -> Sam -> Sam
- arpUp1 :: Chord -> Sig -> Sam -> Sam
- arpDown1 :: Chord -> Sig -> Sam -> Sam
- arpOneOf1 :: Chord -> Sig -> Sam -> Sam
- arpFreqOf1 :: [D] -> Chord -> Sig -> Sam -> Sam
- wall :: D -> Sam -> Sam
- forAirports :: [(D, D, D)] -> Sam -> Sam
- genForAirports :: [(D, D, Sam)] -> Sam
- arpy :: (D -> SE Sig2) -> D -> D -> Int -> [[D]] -> Sam
- metroS :: Bpm -> Sig -> Evt Unit
- toSec :: Bpm -> D -> D
- module Csound.Sam.Ui
- module Csound.Sam.Trig
Documentation
The generic type for samples.
Functor Sample Source # | |
Applicative Sample Source # | |
RenderCsd Sam Source # | |
Fractional a => Fractional (Sample a) Source # | |
Num a => Num (Sample a) Source # | |
RenderCsd (Source Sam) Source # | |
SigSpace a => SigSpace (Sample a) Source # | |
type DurOf Sam # | |
type AtOut Sig Sig2 Sam # | |
type AtOut Sig2 Sig2 Sam # | |
type AtOut Sig (SE Sig) Sam # | |
type AtOut Sig (SE Sig2) Sam # | |
type AtOut Sig2 (SE Sig2) Sam # | |
Lifters
bindBpm :: (Bpm -> a -> SE b) -> Sample a -> Sample b Source #
Lifts bind on stereo signals to samples with BPM.
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.
Constructors
sig2 :: D -> Sig2 -> Sam Source #
Constructs sample from limited stereo signal (duration is in seconds)
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)
Stereo
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
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
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
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).
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
Parabolic envelope that starts and ends at zero and reaches maximum at the center.
Arrange
wide :: D -> Sam -> Sam Source #
Makes the sampler broader. It's reciprocal of str
wide k = str (1 / k)
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 -> [(D, 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.
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
arpOneOf :: Chord -> [D] -> Sam -> Sam Source #
Plays arpeggio of samles with random notes from the chord.
arpFreqOf :: [D] -> Chord -> [D] -> Sam -> Sam Source #
Plays arpeggio of samles with random notes from the chord. We can assign the frequencies of the notes.
arpOneOf1 :: Chord -> Sig -> Sam -> Sam Source #
Plays arpeggio of samles with random notes from the chord.
arpFreqOf1 :: [D] -> 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
UIs
module Csound.Sam.Ui
Triggering samples
module Csound.Sam.Trig
Orphan instances
Loop Sam Source # | |
Limit Sam Source # | |
Rest Sam Source # | |
Stretch Sam Source # | |
Delay Sam Source # | |
Compose Sam Source # | |
Harmony Sam Source # | |
Melody Sam Source # | |
At Sig Sig2 Sam Source # | |
At Sig2 Sig2 Sam Source # | |
MixAt Sig Sig2 Sam Source # | |
MixAt Sig2 Sig2 Sam Source # | |
At Sig (SE Sig) Sam Source # | |
At Sig (SE Sig2) Sam Source # | |
At Sig2 (SE Sig2) Sam Source # | |
MixAt Sig (SE Sig) Sam Source # | |
MixAt Sig (SE Sig2) Sam Source # | |
MixAt Sig2 (SE Sig2) Sam Source # | |