csound-expression-0.3.0: Csound combinator library

CsoundExpr.Opcodes.Table.Readwrit

Description

Read/Write Operations

Synopsis

Documentation

ftloadk :: K k0 => String -> k0 -> Irate -> [Irate] -> SignalOutSource

  • opcode : ftloadk
  • syntax :
   ftloadk "filename", ktrig, iflag, ifn1 [, ifn2] [...]
  • description :

Load a set of previously-allocated tables from a file.

ftload :: String -> Irate -> [Irate] -> SignalOutSource

  • opcode : ftload
  • syntax :
   ftload "filename", iflag, ifn1 [, ifn2] [...]
  • description :

Load a set of previously-allocated tables from a file.

ftsavek :: K k0 => String -> k0 -> Irate -> [Irate] -> SignalOutSource

  • opcode : ftsavek
  • syntax :
   ftsavek "filename", ktrig, iflag, ifn1 [, ifn2] [...]
  • description :

Save a set of previously-allocated tables to a file.

ftsave :: String -> Irate -> [Irate] -> SignalOutSource

  • opcode : ftsave
  • syntax :
   ftsave "filename", iflag, ifn1 [, ifn2] [...]
  • description :

Save a set of previously-allocated tables to a file.

tablecopy :: (K k0, K k1) => k0 -> k1 -> SignalOutSource

  • opcode : tablecopy
  • syntax :
   tablecopy kdft, ksft
  • description :

Simple, fast table copy opcode.

tablegpw :: K k0 => k0 -> SignalOutSource

  • opcode : tablegpw
  • syntax :
   tablegpw kfn
  • description :

Writes a table's guard point.

tableicopy :: Irate -> Irate -> SignalOutSource

  • opcode : tableicopy
  • syntax :
   tableicopy idft, isft
  • description :

Simple, fast table copy opcode.

tableigpw :: Irate -> SignalOutSource

  • opcode : tableigpw
  • syntax :
   tableigpw ifn
  • description :

Writes a table's guard point.

tableimix :: Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> SignalOutSource

  • opcode : tableimix
  • syntax :
   tableimix idft, idoff, ilen, is1ft, is1off, is1g, is2ft, is2off, is2g
  • description :

Mixes two tables.

tableiw :: [Irate] -> Irate -> Irate -> Irate -> SignalOutSource

  • opcode : tableiw
  • syntax :
   tableiw isig, indx, ifn [, ixmode] [, ixoff] [, iwgmode]
  • description :

This opcode operates on existing function tables, changing their contents. tableiw is used when all inputs are init time variables or constants and you only want to run it at the initialization of the instrument. The valid combinations of variable types are shown by the first letter of the variable names.

tablemix :: (K k0, K k1, K k2, K k3, K k4, K k5, K k6, K k7, K k8) => k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> k6 -> k7 -> k8 -> SignalOutSource

  • opcode : tablemix
  • syntax :
   tablemix kdft, kdoff, klen, ks1ft, ks1off, ks1g, ks2ft, ks2off, ks2g
  • description :

Mixes two tables.

tablera :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> ArateSource

  • opcode : tablera
  • syntax :
   ares tablera kfn, kstart, koff
  • description :

These opcode reads tables in sequential locations to an a-rate variable. Some thought is required before using it. It has at least two major, and quite different, applications which are discussed below.

tablewA :: [Irate] -> Arate -> Arate -> Irate -> SignalOutSource

  • opcode : tablew
  • syntax :
   tablew asig, andx, ifn [, ixmode] [, ixoff] [, iwgmode]
   tablew isig, indx, ifn [, ixmode] [, ixoff] [, iwgmode]
   tablew ksig, kndx, ifn [, ixmode] [, ixoff] [, iwgmode]
  • description :

This opcode operates on existing function tables, changing their contents. tablew is for writing at k- or at a-rates, with the table number being specified at init time. The valid combinations of variable types are shown by the first letter of the variable names.

tablewI :: [Irate] -> Irate -> Irate -> Irate -> SignalOutSource

  • opcode : tablew
  • syntax :
   tablew asig, andx, ifn [, ixmode] [, ixoff] [, iwgmode]
   tablew isig, indx, ifn [, ixmode] [, ixoff] [, iwgmode]
   tablew ksig, kndx, ifn [, ixmode] [, ixoff] [, iwgmode]
  • description :

This opcode operates on existing function tables, changing their contents. tablew is for writing at k- or at a-rates, with the table number being specified at init time. The valid combinations of variable types are shown by the first letter of the variable names.

tablewK :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Irate -> SignalOutSource

  • opcode : tablew
  • syntax :
   tablew asig, andx, ifn [, ixmode] [, ixoff] [, iwgmode]
   tablew isig, indx, ifn [, ixmode] [, ixoff] [, iwgmode]
   tablew ksig, kndx, ifn [, ixmode] [, ixoff] [, iwgmode]
  • description :

This opcode operates on existing function tables, changing their contents. tablew is for writing at k- or at a-rates, with the table number being specified at init time. The valid combinations of variable types are shown by the first letter of the variable names.

tablewa :: (K k0, K k1) => k0 -> Arate -> k1 -> KrateSource

  • opcode : tablewa
  • syntax :
   kstart tablewa kfn, asig, koff
  • description :

This opcode writes to a table in sequential locations to and from an a-rate variable. Some thought is required before using it. It has at least two major, and quite different, applications which are discussed below.

tablewktA :: K k0 => [Irate] -> Arate -> Arate -> k0 -> SignalOutSource

  • opcode : tablewkt
  • syntax :
   tablewkt asig, andx, kfn [, ixmode] [, ixoff] [, iwgmode]
   tablewkt ksig, kndx, kfn [, ixmode] [, ixoff] [, iwgmode]
  • description :

This opcode operates on existing function tables, changing their contents. tablewkt uses a k-rate variable for selecting the table number. The valid combinations of variable types are shown by the first letter of the variable names.

tablewktK :: (K k0, K k1, K k2) => [Irate] -> k0 -> k1 -> k2 -> SignalOutSource

  • opcode : tablewkt
  • syntax :
   tablewkt asig, andx, kfn [, ixmode] [, ixoff] [, iwgmode]
   tablewkt ksig, kndx, kfn [, ixmode] [, ixoff] [, iwgmode]
  • description :

This opcode operates on existing function tables, changing their contents. tablewkt uses a k-rate variable for selecting the table number. The valid combinations of variable types are shown by the first letter of the variable names.

tabmorph :: (K k0, K k1, K k2, K k3) => k0 -> k1 -> k2 -> k3 -> [Irate] -> KrateSource

  • opcode : tabmorph
  • syntax :
   kout tabmorph kindex, kweightpoint, ktabnum1, ktabnum2, 
       ifn1, ifn2 [, ifn3, ifn4,... ifnN]
  • description :

tabmorph allows morphing between a set of tables of the same size, by means of a weighted average between two currently selected tables.

tabmorpha :: Arate -> Arate -> Arate -> Arate -> [Irate] -> ArateSource

  • opcode : tabmorpha
  • syntax :
   aout tabmorpha aindex, aweightpoint, atabnum1, atabnum2, 
       ifn1, ifn2 [, ifn3, ifn4,... ifnN]
  • description :

tabmorpha allows morphing between a set of tables of the same size, by means of a weighted average between two currently selected tables.

tabmorphak :: (K k0, K k1, K k2) => Arate -> k0 -> k1 -> k2 -> [Irate] -> ArateSource

  • opcode : tabmorphak
  • syntax :
   aout tabmorphak aindex, kweightpoint, ktabnum1, ktabnum2, 
       ifn1, ifn2 [, ifn3, ifn4,... ifnN]
  • description :

tabmorphak allows morphing between a set of tables of the same size, by means of a weighted average between two currently selected tables.

tabmorphi :: (K k0, K k1, K k2, K k3) => k0 -> k1 -> k2 -> k3 -> [Irate] -> KrateSource

  • opcode : tabmorphi
  • syntax :
   kout tabmorphi kindex, kweightpoint, ktabnum1, ktabnum2, 
       ifn1, ifn2 [, ifn3, ifn4,... ifnN]
  • description :

tabmorphi allows morphing between a set of tables of the same size, by means of a weighted average between two currently selected tables.

tabrec :: (K k0, K k1, K k2, K k3, K k4) => k0 -> k1 -> k2 -> k3 -> [k4] -> SignalOutSource

  • opcode : tabrec
  • syntax :
   tabrec ktrig_start, ktrig_stop, knumtics, kfn, kin1 [,kin2,...,kinN]
  • description :

Records control-rate signals on trigger-temporization basis.

tabplay :: (K k0, K k1, K k2, K k3) => k0 -> k1 -> k2 -> [k3] -> SignalOutSource

  • opcode : tabplay
  • syntax :
   tabplay ktrig, knumtics, kfn, kout1 [,kout2,..., koutN]
  • description :

Plays-back control-rate signals on trigger-temporization basis.