module Csound.Dynamic.Types.CsdFile(
Csd(..), Flags, Orc(..), Sco(..), Plugin(..), Instr(..), InstrBody,
CsdEvent, csdEventStart, csdEventDur, csdEventContent, csdEventTotalDur,
intInstr, alwaysOn
) where
import Csound.Dynamic.Types.Exp
import Csound.Dynamic.Types.Flags
data Csd = Csd
{ Csd -> Flags
csdFlags :: Flags
, Csd -> Orc
csdOrc :: Orc
, Csd -> Sco
csdSco :: Sco
, Csd -> [Plugin]
csdPlugins :: [Plugin]
}
data Orc = Orc
{ Orc -> InstrBody
orcHead :: InstrBody
, Orc -> [Instr]
orcInstruments :: [Instr]
}
type InstrBody = E
data Instr = Instr
{ Instr -> InstrId
instrName :: InstrId
, Instr -> InstrBody
instrBody :: InstrBody
}
data Sco = Sco
{ Sco -> Maybe Double
scoTotalDur :: Maybe Double
, Sco -> [(Int, Gen)]
scoGens :: [(Int, Gen)]
, Sco -> [(InstrId, [CsdEvent])]
scoNotes :: [(InstrId, [CsdEvent])] }
data Plugin = Plugin
{ Plugin -> String
pluginName :: String
, Plugin -> String
pluginContent :: String
}
intInstr :: Int -> E -> Instr
intInstr :: Int -> InstrBody -> Instr
intInstr Int
n InstrBody
expr = InstrId -> InstrBody -> Instr
Instr (Int -> InstrId
intInstrId Int
n) InstrBody
expr
alwaysOn :: InstrId -> (InstrId, [CsdEvent])
alwaysOn :: InstrId -> (InstrId, [CsdEvent])
alwaysOn InstrId
instrId = (InstrId
instrId, [(Double
0, -Double
1, [])])
type CsdEvent = (Double, Double, Note)
csdEventStart :: CsdEvent -> Double
csdEventDur :: CsdEvent -> Double
csdEventContent :: CsdEvent -> Note
csdEventStart :: CsdEvent -> Double
csdEventStart (Double
a, Double
_, [Prim]
_) = Double
a
csdEventDur :: CsdEvent -> Double
csdEventDur (Double
_, Double
a, [Prim]
_) = Double
a
csdEventContent :: CsdEvent -> [Prim]
csdEventContent (Double
_, Double
_, [Prim]
a) = [Prim]
a
csdEventTotalDur :: CsdEvent -> Double
csdEventTotalDur :: CsdEvent -> Double
csdEventTotalDur (Double
start, Double
dur, [Prim]
_) = Double
start Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
dur