haskore-0.1.0.2: The Haskore Computer Music SystemSource codeContentsIndex
Haskore.Interface.CSound.Orchestra
Documentation
data Output out => T out Source
Constructors
Cons Header [InstrBlock out]
show/hide Instances
Output out => Eq (T out)
Output out => Show (T out)
data InstrBlock a Source
Constructors
InstrBlock
instrBlockInstr :: Instrument
instrBlockReverb :: Reverb
instrBlockOutput :: a
instrBlockGlobals :: [(GlobalSig, SigExp)]
show/hide Instances
Eq a => Eq (InstrBlock a)
Show a => Show (InstrBlock a)
type Header = (AudRate, CtrlRate)Source
type AudRate = IntSource
type CtrlRate = IntSource
type SigExp = T SigTermSource
type DelayLine = DelayLineTerm SigExpSource
type Boolean = BooleanTerm SigExpSource
data GlobalSig Source
Constructors
Global EvalRate (SigExp -> SigExp -> SigExp) Int
show/hide Instances
class (Show c, Eq c) => Output c whereSource
Methods
getChannels :: c -> [SigExp]Source
getName :: c -> StringSource
getChannelCount :: c -> IntSource
show/hide Instances
data Mono Source
Constructors
Mono SigExp
show/hide Instances
data Stereo Source
Constructors
Stereo SigExp SigExp
show/hide Instances
data Quad Source
Constructors
Quad SigExp SigExp SigExp SigExp
show/hide Instances
data EvalRate Source
Constructors
NR
CR
AR
show/hide Instances
data Instrument Source
show/hide Instances
type Name = StringSource
sigGen :: Function -> EvalRate -> OutCount -> [SigExp] -> SigExpSource
tableNumber :: Table -> SigExpSource
readGlobal :: GlobalSig -> SigExpSource
rec :: (SigExp -> SigExp) -> SigExpSource
toString :: Output a => T a -> StringSource
saveIA :: Output a => T a -> IO ()Source
save :: Output a => FilePath -> T a -> IO ()Source
channelCount :: Output a => T a -> IntSource
getMultipleOutputs :: SigExp -> [SigExp]Source
noteDur :: SigExpSource
notePit :: SigExpSource
noteVel :: SigExpSource
p1 :: SigExpSource
p2 :: SigExpSource
p3 :: SigExpSource
p4 :: SigExpSource
p5 :: SigExpSource
p6 :: SigExpSource
p7 :: SigExpSource
p8 :: SigExpSource
p9 :: SigExpSource
pField :: Int -> SigExpSource
(<*) :: TreeTerm term => T term -> T term -> BooleanTerm (T term)Source
(<=*) :: TreeTerm term => T term -> T term -> BooleanTerm (T term)Source
(>*) :: TreeTerm term => T term -> T term -> BooleanTerm (T term)Source
(>=*) :: TreeTerm term => T term -> T term -> BooleanTerm (T term)Source
(==*) :: TreeTerm term => T term -> T term -> BooleanTerm (T term)Source
(/=*) :: TreeTerm term => T term -> T term -> BooleanTerm (T term)Source
(&&*) :: Boolean -> Boolean -> BooleanSource
(||*) :: Boolean -> Boolean -> BooleanSource
ifthen :: TreeTerm term => BooleanTerm (T term) -> T term -> T term -> T termSource
constInt :: Int -> SigExpSource
constFloat :: Float -> SigExpSource
constEnum :: Enum a => a -> SigExpSource
pchToHz :: SigExp -> SigExpSource
dbToAmp :: SigExp -> SigExpSource
line :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExpSource
expon :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExpSource
lineSeg :: EvalRate -> SigExp -> SigExp -> SigExp -> [(SigExp, SigExp)] -> SigExpSource
exponSeg :: EvalRate -> SigExp -> SigExp -> SigExp -> [(SigExp, SigExp)] -> SigExpSource
env :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExpSource
phasor :: EvalRate -> SigExp -> SigExp -> SigExpSource
data IndexMode Source
Constructors
RawIndex
NormalIndex
show/hide Instances
tblLookup :: EvalRate -> IndexMode -> SigExp -> SigExp -> SigExpSource
tblLookupI :: EvalRate -> IndexMode -> SigExp -> SigExp -> SigExpSource
osc :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExpSource
oscI :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExpSource
fmOsc :: SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExpSource
fmOscI :: SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExpSource
sampOsc :: SigExp -> SigExp -> SigExp -> SigExpSource
random :: EvalRate -> SigExp -> SigExpSource
randomH :: EvalRate -> SigExp -> SigExp -> SigExpSource
randomI :: EvalRate -> SigExp -> SigExp -> SigExpSource
genBuzz :: SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExpSource
buzz :: SigExp -> SigExp -> SigExp -> SigExp -> SigExpSource
pluck :: SigExp -> SigExp -> PluckDecayMethod -> SigExp -> SigExp -> SigExpSource
data PluckDecayMethod Source
Constructors
PluckSimpleSmooth
PluckStretchSmooth SigExp
PluckSimpleDrum SigExp
PluckStretchDrum SigExp SigExp
PluckWeightedSmooth SigExp SigExp
PluckFilterSmooth
delay :: SigExp -> SigExp -> SigExpSource
vdelay :: SigExp -> SigExp -> SigExp -> SigExpSource
comb :: SigExp -> SigExp -> SigExp -> SigExpSource
alpass :: SigExp -> SigExp -> SigExp -> SigExpSource
reverb :: SigExp -> SigExp -> SigExpSource
delTap :: DelayLine -> SigExp -> SigExpSource
delTapI :: DelayLine -> SigExp -> SigExpSource
type Orc a b = State (OrcState a) bSource
mkSignal :: Output a => EvalRate -> (SigExp -> SigExp -> SigExp) -> Orc a GlobalSigSource
addInstr :: Output a => InstrBlock a -> Orc a ()Source
mkOrc :: Output a => Header -> Orc a () -> T aSource
orc1 :: T StereoSource
test :: IO ()Source
test1 :: StatementDefsSource
Produced by Haddock version 2.7.2