CsoundExpr.Base.Types
- class (IM CsTree a, MO a) => X a
- class X a => K a
- data CsoundFile
- type Flags = String
- data Arate
- data Krate
- data Irate
- data SignalOut
- outList :: [SignalOut] -> SignalOut
- class ToSignal a where
- itime :: Irate
- idur :: Irate
- num :: Irate -> Irate
- string :: IM CsTree a => String -> a
- csd :: Flags -> Header -> EventList Dur SignalOut -> CsoundFile
Documentation
audio signal
control signal
init variable
Output of opcodes that produce no value in csound code (out, outs, xtratim, etc.)
outList :: [SignalOut] -> SignalOutSource
Join several output opcodes
Example :
instr q
a1 upsamp 1
out a1
gaSig = a1
endin
q = outList [out x, gar "Sig" <=> x]
where x = upsamp $ num 1
Rate conversion
Arguments
| :: Flags | flags |
| -> Header | header section |
| -> EventList Dur SignalOut | score section |
| -> CsoundFile | csd file |
Generate csound code
Csound code consists of flags, header section, instruments,
ftables and score. Flags are represeted by String. See
CsoundExpr.Orchestra.Header for more details on header
section. Instruments, ftables and score are generated from
EventList Dur SignalOut. From list of SignalOut notes list
of instruments is derived. Expression-tree structures of
instruments are different from one another. An instrument
can't be transformed into another one only with substitution
of values in lists of expression-tree.
Example (d minor) :
import CsoundExpr
import CsoundExpr.Opcodes
import CsoundExpr.Base.Pitch
flags = "-o dm.wav"
setup = instr0 [
gSr <=> 44100,
gKr <=> 4410,
gKsmps <=> 10,
gNchnls <=> 1]
header = [setup]
sinWave = gen10 4096 [1]
instr :: Irate -> SignalOut
instr x = out $ oscilA [] (num 1000) (cpspch x) sinWave
sco = fmap instr $ line $ map (note 1) [d 0, f 0, a 0, d 1]
main = print $ csd flags header $ toList sco
Example (radiohead - weird fishes, intro) :
import CsoundExpr
import CsoundExpr.Opcodes hiding (delay)
import CsoundExpr.Base.Pitch
mapSnd f (a, b) = (a, f b)
flags = "-d"
setupMono = instr0 [
gSr <=> 44100,
gKr <=> 4410,
gKsmps <=> 10,
gNchnls <=> 1 ]
headerMono = [setupMono]
-- volume levels
v1 = 1.3 * v0
v0 = 7000
-- instruments pluckInstr :: (Irate, Irate) -> SignalOut pluckInstr (amp, pch) = outList [ out $ env <*> wgpluck2 0.75 amp (cpspch pch) (num 0.75) (num 0.5), xtratim 1] where env = linsegrK [0, idur * 0.05, 1, idur * 0.9, 1] 1 0 guitar = pluckInstr . mapSnd (+ (-1)) --chords guitarChord1, guitarChord2, guitarChord3 :: [Irate] -> Score (Irate, Irate) -- volumes 4/4 vs x = map ( * x) $ cycle [v1, v0, v0, v0] -- guitar 1 guitarChord1 = line . map return . zip (vs 1) . concat . replicate 10 ch11 = [d 1, g 0, e 0] ch12 = map ( + 0.02) ch11 ch13 = [a 1, a 0, cs 1] ch14 = [fs 1, b 0, g 0] chSeq1 = line $ map return $ [ch11, ch12, ch13, ch14] -- guitar 2 guitarChord2 = line . map return . zip (vs 0.5) . concat . replicate 6 . arpeggi where arpeggi x = x ++ take 2 x ch21 = [g 0, d 1, e 1] ch22 = map (+ 0.02) ch21 ch23 = [cs 1, e 1, a 1] ch24 = [d 1, g 1, e 1] chSeq2 = line $ map return $ [ch21, ch22, ch23, ch24] -- guitar 3 guitarChord3 = line . map return . zip (vs 0.2) . concat . replicate 6 . arpeggi where arpeggi x = take 2 x ++ x ch31 = [e 1, g 1, b 1] ch32 = map (+ 0.02) ch31 ch33 = [fs 1, a 1, cs 2] ch34 = [d 2, g 1, b 1] chSeq3 = line $ map return $ [ch31, ch32, ch33, ch34] -- scores scoG1 = fmap guitar $ chSeq1 >>= guitarChord1 scoG2 = fmap guitar $ chSeq2 >>= guitarChord2 scoG3 = fmap guitar $ chSeq3 >>= guitarChord3 scoG2intro = cut (3*30) (4*30) scoG2 intro = chord [scoG1, scoG3, delay (3*30) scoG2intro] chords = loop 3 $ chord [scoG1, scoG2, scoG3] sco = stretch 0.17 $ intro +:+ chords main = print $ csd flags headerMono $ toList sco