Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data GE a
- type Dep a = DepT GE a
- data History = History {
- genMap :: !GenMap
- writeGenMap :: !WriteGenMap
- globalGenCounter :: !Int
- stringMap :: !StringMap
- sfMap :: !SfMap
- midiMap :: !(MidiMap GE)
- globals :: !Globals
- instrs :: !Instrs
- udoPlugins :: ![UdoPlugin]
- namedInstrs :: !NamedInstrs
- midis :: ![MidiAssign]
- midiCtrls :: ![MidiCtrl]
- totalDur :: !(Maybe TotalDur)
- alwaysOnInstrs :: ![InstrId]
- notes :: ![(InstrId, CsdEvent)]
- userInstr0 :: !(Dep ())
- bandLimitedMap :: !BandLimitedMap
- cache :: !(Cache GE)
- guis :: !Guis
- oscListenPorts :: !OscListenPorts
- cabbageGui :: !(Maybe Lang)
- macrosInits :: !MacrosInits
- withOptions :: (Options -> a) -> GE a
- withHistory :: (History -> a) -> GE a
- getOptions :: GE Options
- evalGE :: Options -> GE a -> IO a
- execGE :: Options -> GE a -> IO History
- getHistory :: GE History
- putHistory :: History -> GE ()
- onGlobals :: UpdField Globals a
- bpmVar :: Var
- data MidiAssign = MidiAssign MidiType Channel InstrId
- data Msg = Msg
- renderMidiAssign :: Monad m => MidiAssign -> DepT m ()
- saveMidi :: MidiAssign -> GE ()
- saveToMidiInstr :: MidiType -> Channel -> Dep () -> GE ()
- data MidiCtrl = MidiCtrl E E E
- saveMidiCtrl :: MidiCtrl -> GE ()
- renderMidiCtrl :: Monad m => MidiCtrl -> DepT m ()
- saveAlwaysOnInstr :: InstrId -> GE ()
- onInstr :: UpdField Instrs a
- saveUserInstr0 :: Dep () -> GE ()
- getSysExpr :: InstrId -> GE (Dep ())
- saveNamedInstr :: Text -> InstrBody -> GE ()
- data TotalDur
- = ExpDur E
- | InfiniteDur
- pureGetTotalDurForF0 :: Maybe TotalDur -> Double
- getTotalDurForTerminator :: GE E
- setDurationForce :: E -> GE ()
- setDuration :: E -> GE ()
- setDurationToInfinite :: GE ()
- addNote :: InstrId -> CsdEvent -> GE ()
- data GenId
- saveGen :: Gen -> GE Int
- saveTabs :: [Gen] -> GE E
- getNextGlobalGenId :: GE Int
- saveWriteGen :: Gen -> GE E
- saveWriteTab :: Int -> GE E
- saveSf :: SfSpec -> GE Int
- sfTable :: History -> [(SfSpec, Int)]
- saveBandLimitedWave :: BandLimited -> GE BandLimitedId
- saveStr :: Text -> GE E
- type GetCache a b = a -> Cache GE -> Maybe b
- type SetCache a b = a -> b -> Cache GE -> Cache GE
- withCache :: TotalDur -> GetCache key val -> SetCache key val -> key -> GE val -> GE val
- newGuiHandle :: GE GuiHandle
- saveGuiRoot :: Panel -> GE ()
- saveDefKeybdPanel :: GE ()
- appendToGui :: GuiNode -> DepT GE () -> GE ()
- newGuiVar :: GE (Var, GuiHandle)
- getPanels :: History -> [Panel]
- guiHandleToVar :: GuiHandle -> Var
- guiInstrExp :: GE (DepT GE ())
- listenKeyEvt :: KeyEvt -> GE Var
- data Key
- = CharKey Char
- | F1
- | F2
- | F3
- | F4
- | F5
- | F6
- | F7
- | F8
- | F9
- | F10
- | F11
- | F12
- | Scroll
- | CapsLook
- | LeftShift
- | RightShift
- | LeftCtrl
- | RightCtrl
- | Enter
- | LeftAlt
- | RightAlt
- | LeftWinKey
- | RightWinKey
- | Backspace
- | ArrowUp
- | ArrowLeft
- | ArrowRight
- | ArrowDown
- | Insert
- | Home
- | PgUp
- | Delete
- | End
- | PgDown
- | NumLock
- | NumDiv
- | NumMul
- | NumSub
- | NumHome
- | NumArrowUp
- | NumPgUp
- | NumArrowLeft
- | NumSpace
- | NumArrowRight
- | NumEnd
- | NumArrowDown
- | NumPgDown
- | NumIns
- | NumDel
- | NumEnter
- | NumPlus
- | Num7
- | Num8
- | Num9
- | Num4
- | Num5
- | Num6
- | Num1
- | Num2
- | Num3
- | Num0
- | NumDot
- data KeyEvt
- data Guis = Guis {
- guiStateNewId :: Int
- guiStateInstr :: DepT GE ()
- guiStateToDraw :: [GuiNode]
- guiStateRoots :: [Panel]
- guiKeyEvents :: KeyCodeMap
- getKeyEventListener :: GE (Maybe Instr)
- getOscPortHandle :: Int -> GE E
- data MacrosInit
- = MacrosInitDouble { }
- | MacrosInitString { }
- | MacrosInitInt { }
- readMacrosDouble :: Text -> Double -> GE E
- readMacrosString :: Text -> Text -> GE E
- readMacrosInt :: Text -> Int -> GE E
- cabbage :: Cab -> GE ()
- simpleHrtfmove :: E -> E -> E -> E -> E -> E -> GE (E, E)
- simpleHrtfstat :: E -> E -> E -> E -> E -> GE (E, E)
- addUdoPlugin :: UdoPlugin -> GE ()
- renderUdoPlugins :: History -> IO Text
Documentation
Instances
History | |
|
withOptions :: (Options -> a) -> GE a Source #
withHistory :: (History -> a) -> GE a Source #
getOptions :: GE Options Source #
getHistory :: GE History Source #
putHistory :: History -> GE () Source #
Globals
Midi
Instances
DirtyMulti b => DirtyMulti (Msg -> b) Source # | |
Defined in Csound.Typed.Types.Lift | |
DirtySingle b => DirtySingle (Msg -> b) Source # | |
Defined in Csound.Typed.Types.Lift | |
Procedure b => Procedure (Msg -> b) Source # | |
Defined in Csound.Typed.Types.Lift procedureGE :: GE ([E] -> Dep ()) -> Msg -> b | |
PureMulti b => PureMulti (Msg -> b) Source # | |
Defined in Csound.Typed.Types.Lift | |
PureSingle b => PureSingle (Msg -> b) Source # | |
Defined in Csound.Typed.Types.Lift pureSingleGE :: GE ([E] -> E) -> Msg -> b |
renderMidiAssign :: Monad m => MidiAssign -> DepT m () Source #
saveMidi :: MidiAssign -> GE () Source #
saveMidiCtrl :: MidiCtrl -> GE () Source #
Instruments
saveAlwaysOnInstr :: InstrId -> GE () Source #
saveUserInstr0 :: Dep () -> GE () Source #
Named instruments
Total duration
setDurationForce :: E -> GE () Source #
setDuration :: E -> GE () Source #
setDurationToInfinite :: GE () Source #
Notes
GEN routines
Instances
Generic GenId | |
Show GenId | |
Eq GenId | |
Ord GenId | |
type Rep GenId | |
Defined in Csound.Dynamic.Types.Exp type Rep GenId = D1 ('MetaData "GenId" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.9.1-1cJbmtshgbjKoGghhay83W" 'False) (C1 ('MetaCons "IntGenId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "StringGenId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
Sf2
Band-limited waves
Strings
Cache
Guis
saveGuiRoot :: Panel -> GE () Source #
saveDefKeybdPanel :: GE () Source #
guiHandleToVar :: GuiHandle -> Var Source #
Keys.
Keyboard events.
Guis | |
|
OSC
Macros
data MacrosInit Source #
Instances
Show MacrosInit Source # | |
Defined in Csound.Typed.GlobalState.Elements showsPrec :: Int -> MacrosInit -> ShowS # show :: MacrosInit -> String # showList :: [MacrosInit] -> ShowS # | |
Eq MacrosInit Source # | |
Defined in Csound.Typed.GlobalState.Elements (==) :: MacrosInit -> MacrosInit -> Bool # (/=) :: MacrosInit -> MacrosInit -> Bool # | |
Ord MacrosInit Source # | |
Defined in Csound.Typed.GlobalState.Elements compare :: MacrosInit -> MacrosInit -> Ordering # (<) :: MacrosInit -> MacrosInit -> Bool # (<=) :: MacrosInit -> MacrosInit -> Bool # (>) :: MacrosInit -> MacrosInit -> Bool # (>=) :: MacrosInit -> MacrosInit -> Bool # max :: MacrosInit -> MacrosInit -> MacrosInit # min :: MacrosInit -> MacrosInit -> MacrosInit # |
Cabbage Guis
Hrtf pan
Udo plugins
addUdoPlugin :: UdoPlugin -> GE () Source #