module Language.XDsp.Implementations.Csound (
S (..)
,BusType (..)
,HostOut (..)
,RType
,defaultRType
,unifyCsd
,writeHeader
,makeInstrument
,TList
,unTList'
,mkTbl
,writeCard
,module Language.XDsp.Semantics.CsoundExt
)
where
import Language.XDsp.Semantics
import Language.XDsp.Semantics.CsoundExt hiding (CsOscil (..), CsOscili (..), CsSum (..))
import qualified Language.XDsp.Semantics.CsoundExt as CSE
import Data.Char
import Data.Data
import Data.List (intersperse, intercalate)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, catMaybes)
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.TypeLevel.Num ((:>=:), Nat, toInt)
import Control.Monad.RWS
import Control.Applicative
import Control.Arrow
import Text.Printf
data CVar =
Cnst Double
| CStr String
| CVar String
deriving (Eq, Ord, Show, Read)
data VarType =
A
| K
| I
| F
| T
| IC
| St
| U
| Tp VarType VarType
| T3 VarType VarType VarType
| T4 VarType VarType VarType VarType
| CList VarType
deriving (Eq, Ord, Read, Show)
mkChr :: VarType -> Char
mkChr T = 'f'
mkChr IC = 'i'
mkChr St = 'i'
mkChr x = toLower . head . show $ x
getLbl :: CVar -> String
getLbl (Cnst x) = show x
getLbl (CStr s) = show s
getLbl (CVar s) = s
class ArgListBuilder r where
appendToList :: [String] -> r
instance ArgListBuilder [String] where
appendToList = reverse
instance (Varable a, ArgListBuilder r) => ArgListBuilder (a -> r) where
appendToList arg = appendToList . (\acc a -> getVarLbl a : acc) arg
mkOp0 :: Varable out => String -> S n out
mkOp0 opname = do
(out, outName) <- genName
tellOrc $ printf "%s %s\n" outName opname
return out
mkOp1 :: (Varable a, Varable out) => String -> a -> S n out
mkOp1 opname a1 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname (getVarLbl a1)
return out
mkOp2 opname a1 a2 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2)
return out
mkOp3 opname a1 a2 a3 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3)
return out
mkOp4 opname a1 a2 a3 a4 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4)
return out
mkOp5 opname a1 a2 a3 a4 a5 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5)
return out
mkOp6 opname a1 a2 a3 a4 a5 a6 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6)
return out
mkOp7 opname a1 a2 a3 a4 a5 a6 a7 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7)
return out
mkOp8 opname a1 a2 a3 a4 a5 a6 a7 a8 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7 a8)
return out
mkOp9 opname a1 a2 a3 a4 a5 a6 a7 a8 a9 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7 a8 a9)
return out
mkOp10 opname a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7 a8 a9 a10)
return out
mkOp11 opname a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11)
return out
mkOp12 opname a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12)
return out
mkOp13 opname a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13)
return out
mkOp17 opname a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 = do
(out, outName) <- genName
tellOrc $ printf "%s %s %s\n" outName opname
(argCleaner $ appendToList [] a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17)
return out
argCleaner :: [String] -> String
argCleaner = intercalate ", " . filter (Prelude.not . null)
mkOp14 = error "mkOp14"
mkOp15 = error "mkOp15"
mkOp16 = error "mkOp16"
mkOp18 = error "mkOp18"
mkOp19 = error "mkOp19"
mkOp22 = error "mkOp22"
mkOp26 = error "mkOp26"
mkOp32 = error "mkOp32"
mkOp83 = error "mkOp83"
mkOp99 = error "mkOp99"
mkOp51 = error "mkOp51"
mkOp34 = error "mkOp34"
mkOp43 = error "mkOp43"
data Card = Card VarType [String] deriving (Eq, Read, Show)
card2str :: Card -> String
card2str (Card typ args) = mkChr typ : unwords args ++ "\n"
writeCard :: Card -> S n ()
writeCard = tellSco . card2str
mkTbl :: Int -> Double -> Int -> Int -> [Double] -> Card
mkTbl nm time sz gen args = Card T $
show nm:show time:show sz:show gen:map show args
mkScoreBuf :: Int -> Int -> S n ()
mkScoreBuf nm sz = writeCard $ mkTbl nm 0 sz 17 [0,0]
data CardM = CardM VarType String String deriving (Eq, Ord, Show)
cacheBuf :: String -> Int -> CardM
cacheBuf lbl = CardM T lbl . show
data BusType = KBus | TblBus Int deriving (Eq, Read, Show)
data HostOut = HostOut {
busType :: BusType,
busLbl :: String,
busName :: String } deriving (Eq, Read, Show)
data CacheKey =
CKC CardM
deriving (Eq, Ord, Show)
type WCache = M.Map CacheKey CVar
type GenMap = M.Map VarType Int
type ICache = S.Set Int
data SState = SState {
wcache :: WCache
,genMap :: GenMap
,iCache :: ICache}
type ScoType = TL.Text
type OrcType = TL.Text
type HostType = [HostOut]
type WType = (ScoType, OrcType, HostType)
type RType = (Integer, Integer)
defaultRType = (44100,16)
newtype S n a = S { unS :: RWS RType WType SState a }
deriving (Functor, Applicative, Monad, Typeable)
instance MonadFix (S n) where
mfix f = S $ mfix (unS . f)
instance MonadState (S n) where
type StateType (S n) = SState
get = S get
put = S . put
instance MonadWriter (S n) where
type WriterType (S n) = WType
tell = S . tell
listen = S . listen . unS
pass = S . pass . unS
instance MonadReader (S n) where
type EnvType (S n) = RType
ask = S ask
local f = S . local f . unS
csdHeader =
"<CsoundSynthesizer>\n\
\<CsOptions>\n\
\%s\n\
\</CsOptions>\n"
getGen :: S n GenMap
getGen = fmap genMap get
putGen :: GenMap -> S n ()
putGen newstate = modify (\ss -> ss {genMap = newstate})
cache :: CacheKey -> CVar -> S n ()
cache key val = do
SState cmap gen imap <- get
put $ SState (M.insert key val cmap) gen imap
cacheInstr :: Int -> S n ()
cacheInstr n = modify (\ss -> let ic' = S.insert n (iCache ss) in ss { iCache = ic' })
instrInCache :: Int -> S n Bool
instrInCache n = do
(SState _ _ imap) <- get
return $ S.member n imap
tellOrc :: String -> S n ()
tellOrc s = tell (TL.pack s,mempty, mempty)
tellSco :: String -> S n ()
tellSco s = tell (mempty,TL.pack s,mempty)
tellHost :: HostOut -> S n ()
tellHost s = tell (mempty,mempty, [s])
runS :: S n a -> RType -> (a, SState, WType)
runS e rt = runRWS (unS e) rt (SState M.empty M.empty S.empty)
evalS :: S n a -> RType -> a
evalS e rt = let (a,_,_) = runS e rt in a
getWritten :: RType -> S n x -> WType
getWritten rt e = let (_,_,w) = runS e rt in w
unifyCsd :: [String] -> RType -> S n x -> (TL.Text, [HostOut])
unifyCsd args r = unifyCsd' args . getWritten r
unifyCsd' :: [String] -> WType -> (TL.Text, [HostOut])
unifyCsd' args (orc, sco, host) = (csd, host)
where
oH = TL.pack "<CsInstruments>\n"
oF = TL.pack "\n</CsInstruments>\n"
sH = TL.pack "<CsScore>\n"
sF = TL.pack "\ne\n</CsScore>\n</CsoundSynthesizer>\n"
csd = TL.concat [TL.pack (printf csdHeader (unwords args))
,oH ,orc ,oF ,sH ,sco ,sF]
class Varable s where
genName :: S n (s, String)
getVarLbl :: s -> String
instance Varable s => Var s where
type VarRep s = String
getVarRep s = getVarLbl s
class Varable s => PVar s where
class Varable s => KVar s where
mkName :: VarType -> S n Int
mkName typ = do
gen <- getGen
let num = fromMaybe 1 $ M.lookup typ gen
putGen $ M.alter (const $ Just (succ num)) typ gen
return num
instance Dsp (S n) where
data (ASig (S n)) = S_A CVar
data (KSig (S n)) = S_K CVar
data (INum (S n)) = S_I CVar
getSr = fst <$> ask
getKsmps = snd <$> ask
instance Constants (S n) where
cnst = return . S_I . Cnst
ckig = return . S_K . Cnst
csig = return . S_A . Cnst
instance Cast (S n) where
ik ivar = mkOp1 "=" ivar
ia ivar = mkOp1 "=" ivar
ki kvar = do
(out, outname) <- genName
tellOrc $ printf "%s = i(%s)\n" outname (getVarLbl kvar)
return out
instance Varable (ASig (S n)) where
genName = do
SState omap gen imap <- get
let num = fromMaybe 1 $ M.lookup A gen
nm = 'a' : show num
put $ SState omap (M.alter (const $ Just (succ num)) A gen) imap
return (S_A $ CVar nm, nm)
getVarLbl (S_A c) = getLbl c
instance PVar (ASig (S n)) where
instance Varable (KSig (S n)) where
genName = do
SState omap gen imap <- get
let num = fromMaybe 1 $ M.lookup K gen
nm = 'k' : show num
put $ SState omap (M.alter (const $ Just (succ num)) K gen) imap
return (S_K $ CVar nm, nm)
getVarLbl (S_K c) = getLbl c
instance PVar (KSig (S n)) where
instance KVar (KSig (S n)) where
instance Varable (INum (S n)) where
genName = do
SState omap gen imap <- get
let num = fromMaybe 1 $ M.lookup I gen
nm = 'i' : show num
put $ SState omap (M.alter (const $ Just (succ num)) I gen) imap
return (S_I $ CVar nm, nm)
getVarLbl (S_I c) = getLbl c
instance Varable () where
genName = return ((), "")
getVarLbl _ = "()"
instance Varable String where
genName = error "Can't call 'genName' on String directly"
getVarLbl s = '"' : s ++ "\""
instance Varable (VString (S n)) where
genName = do
SState omap gen imap <- get
let num = fromMaybe 1 $ M.lookup St gen
nm = 'S' : show num
put $ SState omap (M.alter (const $ Just (succ num)) St gen) imap
return (S_VS $ CVar nm, nm)
getVarLbl (S_VS c) = getLbl c
instance KVar (VString (S n)) where
instance (Varable a, Varable b) => Varable (a,b) where
genName = do
(o1,nm1) <- genName
(o2,nm2) <- genName
return ((o1,o2), nm1 ++ ", " ++ nm2)
getVarLbl (a,b) = getVarLbl a ++ ", " ++ getVarLbl b
instance (Varable a, Varable b, Varable c) =>
Varable (a,b,c) where
genName = do
(o1,nm1) <- genName
(o2,nm2) <- genName
(o3,nm3) <- genName
return ((o1,o2,o3), intercalate ", " [nm1, nm2, nm3])
getVarLbl (a,b,c) =
intercalate ", " [getVarLbl a, getVarLbl b,getVarLbl c]
instance (Varable a, Varable b, Varable c, Varable d) => Varable (a,b,c,d) where
genName = do
(o1,nm1) <- genName
(o2,nm2) <- genName
(o3,nm3) <- genName
(o4,nm4) <- genName
return ((o1,o2,o3,o4), intercalate ", " [nm1, nm2, nm3, nm4])
getVarLbl (a,b,c,d) =
intercalate ", " [getVarLbl a, getVarLbl b,getVarLbl c, getVarLbl d]
instance Varable a => Varable [a] where
genName = error "Can't generate names for arbitrary lists"
getVarLbl = intercalate ", " . map getVarLbl
instance forall d a. (Varable a, Nat d) => Varable (TList d a) where
genName = do
outss <- replicateM (toInt (undefined :: d)) genName
return (TList $ map fst outss, intercalate ", " $ map snd outss)
getVarLbl = intercalate ", " . map getVarLbl . unTList
instance KVar (INum (S n)) where
instance PVS (S n) where
data FSig (S n) = S_FSig CVar
instance Varable (FSig (S n)) where
genName = do
SState omap gen imap <- get
let num = fromMaybe 1 $ M.lookup F gen
nm = 'f' : show num
put $ SState omap (M.alter (const $ Just (succ num)) F gen) imap
return (S_FSig $ CVar nm, nm)
getVarLbl (S_FSig c) = getLbl c
instance Varable Double where
genName = error "genName shouldn't be called with Doubles"
getVarLbl = show
instance StringVar (S n) where
data VString (S n) = S_VS CVar
fromStr = S_VS . CStr
instance CsoundClass (S n) where
nchnls n = tellOrc (printf "nchnls = %i\n" n) >> return n
set0dbfs n = tellOrc (printf "0dbfs = %f\n" n) >> return n
instance CsFunctions (ASig (S n)) where
octcps (S_A a) = S_A . CVar $ printf "(octcps(%s))" (getLbl a)
octpch (S_A a) = S_A . CVar $ printf "(octpch(%s))" (getLbl a)
cpspch (S_A a) = S_A . CVar $ printf "(cpspch(%s))" (getLbl a)
cpsoct (S_A a) = S_A . CVar $ printf "(cpsoct(%s))" (getLbl a)
pchoct (S_A a) = S_A . CVar $ printf "(pchoct(%s))" (getLbl a)
pchcps (S_A a) = S_A . CVar $ printf "(pchcps(%s))" (getLbl a)
instance CsFunctions (KSig (S n)) where
octcps (S_K a) = S_K . CVar $ printf "(octcps(%s))" (getLbl a)
octpch (S_K a) = S_K . CVar $ printf "(octpch(%s))" (getLbl a)
cpspch (S_K a) = S_K . CVar $ printf "(cpspch(%s))" (getLbl a)
cpsoct (S_K a) = S_K . CVar $ printf "(cpsoct(%s))" (getLbl a)
pchoct (S_K a) = S_K . CVar $ printf "(pchoct(%s))" (getLbl a)
pchcps (S_K a) = S_K . CVar $ printf "(pchcps(%s))" (getLbl a)
instance CsFunctions (INum (S n)) where
octcps (S_I a) = S_I . CVar $ printf "(octcps(%s))" (getLbl a)
octpch (S_I a) = S_I . CVar $ printf "(octpch(%s))" (getLbl a)
cpspch (S_I a) = S_I . CVar $ printf "(cpspch(%s))" (getLbl a)
cpsoct (S_I a) = S_I . CVar $ printf "(cpsoct(%s))" (getLbl a)
pchoct (S_I a) = S_I . CVar $ printf "(pchoct(%s))" (getLbl a)
pchcps (S_I a) = S_I . CVar $ printf "(pchcps(%s))" (getLbl a)
instance Show (ASig (S n)) where
show (S_A s) = show s
instance Eq (ASig (S n)) where
(S_A a) == (S_A b) = a == b
instance Num (ASig (S n)) where
(S_A a) + (S_A b) = S_A . CVar $ printf "(%s + %s)" (getLbl a) (getLbl b)
(S_A a) (S_A b) = S_A . CVar $ printf "(%s - %s)" (getLbl a) (getLbl b)
(S_A a) * (S_A b) = S_A . CVar $ printf "(%s * %s)" (getLbl a) (getLbl b)
abs (S_A a) = S_A . CVar $ printf "(abs %s)" (getLbl a)
signum = error "signum called on (ASig (S n))"
fromInteger = S_A . Cnst . fromInteger
instance Fractional (ASig (S n)) where
(S_A a) / (S_A b) = S_A . CVar $ printf "(%s / %s)" (getLbl a) (getLbl b)
fromRational = S_A . Cnst . fromRational
instance Show (KSig (S n)) where
show (S_K s) = show s
instance Eq (KSig (S n)) where
(S_K a) == (S_K b) = a == b
instance Num (KSig (S n)) where
(S_K a) + (S_K b) = S_K . CVar $ printf "(%s + %s)" (getLbl a) (getLbl b)
(S_K a) (S_K b) = S_K . CVar $ printf "(%s - %s)" (getLbl a) (getLbl b)
(S_K a) * (S_K b) = S_K . CVar $ printf "(%s * %s)" (getLbl a) (getLbl b)
abs (S_K a) = S_K . CVar $ printf "(abs %s)" (getLbl a)
signum = error "signum called on (KSig (S n))"
fromInteger = S_K . Cnst . fromInteger
instance Fractional (KSig (S n)) where
(S_K a) / (S_K b) = S_K . CVar $ printf "(%s / %s)" (getLbl a) (getLbl b)
fromRational = S_K . Cnst . fromRational
instance Show (INum (S n)) where
show (S_I s) = show s
instance Eq (INum (S n)) where
(S_I a) == (S_I b) = a == b
instance Num (INum (S n)) where
(S_I (Cnst a)) + (S_I (Cnst b)) = S_I $ Cnst (a+b)
(S_I a) + (S_I b) = S_I . CVar $ printf "(%s + %s)" (getLbl a) (getLbl b)
(S_I (Cnst a)) (S_I (Cnst b)) = S_I $ Cnst (ab)
(S_I a) (S_I b) = S_I . CVar $ printf "(%s - %s)" (getLbl a) (getLbl b)
(S_I (Cnst a)) * (S_I (Cnst b)) = S_I $ Cnst (a*b)
(S_I a) * (S_I b) = S_I . CVar $ printf "(%s * %s)" (getLbl a) (getLbl b)
abs (S_I a) = S_I . CVar $ printf "(abs %s)" (getLbl a)
signum = error "signum called on (INum (S n))"
fromInteger = S_I . Cnst . fromInteger
instance Fractional (INum (S n)) where
(S_I (Cnst a)) / (S_I (Cnst b)) = S_I . Cnst $ a/b
(S_I a) / (S_I b) = S_I . CVar $ printf "(%s / %s)" (getLbl a) (getLbl b)
fromRational = S_I . Cnst . fromRational
instance Show s => Show ((S n) s) where
show s = show $ evalS s defaultRType
instance Eq e => Eq ((S n) e) where
e1 == e2 = evalS ((==) <$> e1 <*> e2) defaultRType
instance Num e => Num ((S n) e) where
e1 + e2 = (+) <$> e1 <*> e2
e1 e2 = () <$> e1 <*> e2
e1 * e2 = (*) <$> e1 <*> e2
abs = fmap Prelude.abs
signum = fmap signum
fromInteger = pure . fromInteger
instance Fractional e => Fractional ((S n) e) where
e1 / e2 = (/) <$> e1 <*> e2
recip = fmap recip
fromRational = pure . fromRational
instance Varable a => Asn (S n) a where
asn = mkOp1 "="
instance Out (S n) where
out = tellOrc . printf " out %s\n" . getVarLbl
outs a1 a2 = do
(tellOrc $ printf " outs %s, %s\n" (getVarLbl a1) (getVarLbl a2))
outq a1 a2 a3 a4 = do
(tellOrc $ printf " outs %s, %s, %s, %s\n"
(getVarLbl a1) (getVarLbl a2) (getVarLbl a3) (getVarLbl a4))
outo a1 a2 a3 a4 a5 a6 a7 a8 = do
(tellOrc $ printf " outs %s, %s, %s, %s, %s, %s, %s, %s\n"
(getVarLbl a1) (getVarLbl a2) (getVarLbl a3) (getVarLbl a4)
(getVarLbl a5) (getVarLbl a6) (getVarLbl a7) (getVarLbl a8))
instance Buffer (S n) where
type Buf (S n) = INum (S n)
emptyBuffer sz = do
bufNum <- mkName T
mkScoreBuf bufNum sz
return $ fromIntegral bufNum
instance (Varable a) => BufferR (S n) a a where
lookupAt = flip (mkOp2 "tablei")
instance VBuf (S n) where
vbuf lbl sz = do
(SState cmap gen imap) <- get
case M.lookup (CKC $ cacheBuf lbl sz) cmap of
Just nm -> return $ S_I nm
Nothing -> do
bufNum <- mkName T
mkScoreBuf bufNum sz
tellHost . HostOut (TblBus sz) lbl $ show bufNum
let res = Cnst $ fromIntegral bufNum
cache (CKC $ cacheBuf lbl sz) res
return $ S_I res
mkOp str l r = printf ("(%s " ++ str ++ " %s)") (getLbl l) (getLbl r)
instance RCmpr (KSig (S n)) where
data RBool (KSig (S n)) = K_Bool String
req (S_K l) (S_K r) = K_Bool $ mkOp "==" l r
rne (S_K l) (S_K r) = K_Bool $ mkOp "!=" l r
rlt (S_K l) (S_K r) = K_Bool $ mkOp "<" l r
rle (S_K l) (S_K r) = K_Bool $ mkOp "<=" l r
rgt (S_K l) (S_K r) = K_Bool $ mkOp ">" l r
rge (S_K l) (S_K r) = K_Bool $ mkOp ">=" l r
instance RCmpr (INum (S n)) where
data RBool (INum (S n)) = I_Bool String
req (S_I l) (S_I r) = I_Bool $ mkOp "==" l r
rne (S_I l) (S_I r) = I_Bool $ mkOp "!=" l r
rlt (S_I l) (S_I r) = I_Bool $ mkOp "<" l r
rle (S_I l) (S_I r) = I_Bool $ mkOp "<=" l r
rgt (S_I l) (S_I r) = I_Bool $ mkOp ">" l r
rge (S_I l) (S_I r) = I_Bool $ mkOp ">=" l r
instance Varable a => RCtrl (S n) (KSig (S n)) a where
rIf (K_Bool b) m = runIf1 b m
rIfElse (K_Bool b) m1 m2 = runIf b m1 m2
instance Varable a => RCtrl (S n) (INum (S n)) a where
rIf (I_Bool b) m = runIf1 b m
rIfElse (I_Bool b) m1 m2 = runIf b m1 m2
runIf1 test m1 = do
tellOrc $ printf "if %s then\n" test
a <- m1
tellOrc "endif\n"
return a
runIf test m1 m2 = do
tellOrc $ printf "if %s then\n" test
a <- m1
let aLbl = getVarRep a
tellOrc "else\n"
b <- m2
let bLbl = getVarRep b
tellOrc $ printf "%s = %s\n" aLbl bLbl
tellOrc "endif\n"
return a
instance (Nat m, Nat n, Show n, m :>=: n) => NumArgs S m n where
getArg n = return . S_I . CVar $ 'p': show n
instance LblBlock (S n) where
type ArgTag (S n) = n
type ArgTyp (S n) = Either String Double
data Block (S n) = Instr Int
lblBlock num e = do
isCached <- instrInCache num
when (Prelude.not isCached) $ do
tellOrc (printf "instr %d\n" num) >> e >> tellOrc "endin\n\n"
clearBlockData
cacheInstr num
return $ Instr num
runBlock = runBlock'
getArgVal :: Either String Double -> String
getArgVal = either show show
makeInstrument :: S n () -> S n (Block (S n))
makeInstrument e = do
SState _ _ imap <- get
maybe (lblBlock 1 e) (\(n, _) -> lblBlock (n+1) e) $ S.maxView imap
clearBlockData :: S n ()
clearBlockData = do
(SState cmap genmap imap) <- get
let cmap' = M.mapMaybeWithKey cmf cmap
genmap' = M.mapMaybeWithKey gmf genmap
put $ SState cmap' genmap' imap
where
cmf k v = Just v
gmf T n = Just n
gmf _ _ = Nothing
runBlock' ::
Block (S n)
-> Double
-> Double
-> TList m (Either String Double)
-> S n ()
runBlock' (Instr blkLbl) startIn dur args =
writeCard . Card IC $ [show blkLbl, show startIn, show dur]
++ map getArgVal (unTList args)
writeHeader :: Int -> Double -> S n ()
writeHeader nc dbfs = do
(sr,ksmps) <- ask
setSR sr
setKSmps ksmps
nchnls nc
set0dbfs dbfs
return ()
setSR n = tellOrc (printf "sr = %i\n" n) >> return n
setKSmps n = tellOrc (printf "ksmps = %i\n" n) >> return n
instance Math (S n) (ASig (S n)) where
log2 (S_A a) = asn $ S_A . CVar $ printf "(logbtwo(%s))" (getLbl a)
sqrt (S_A a) = asn $ S_A . CVar $ printf "(sqrt(%s))" (getLbl a)
int (S_A a) = asn $ S_A . CVar $ printf "(int(%s))" (getLbl a)
frac (S_A a) = asn $ S_A . CVar $ printf "(frac(%s))" (getLbl a)
floor (S_A a) = asn $ S_A . CVar $ printf "(floor(%s))" (getLbl a)
instance Math (S n) (KSig (S n)) where
log2 (S_K a) = asn $ S_K . CVar $ printf "(logbtwo(%s))" (getLbl a)
sqrt (S_K a) = asn $ S_K . CVar $ printf "(sqrt(%s))" (getLbl a)
int (S_K a) = asn $ S_K . CVar $ printf "(int(%s))" (getLbl a)
frac (S_K a) = asn $ S_K . CVar $ printf "(frac(%s))" (getLbl a)
floor (S_K a) = asn $ S_K . CVar $ printf "(floor(%s))" (getLbl a)
instance Math (S n) (INum (S n)) where
log2 (S_I a) = asn $ S_I . CVar $ printf "(logbtwo(%s))" (getLbl a)
sqrt (S_I a) = asn $ S_I . CVar $ printf "(sqrt(%s))" (getLbl a)
int (S_I a) = asn $ S_I . CVar $ printf "(int(%s))" (getLbl a)
frac (S_I a) = asn $ S_I . CVar $ printf "(frac(%s))" (getLbl a)
floor (S_I a) = asn $ S_I . CVar $ printf "(floor(%s))" (getLbl a)
instance Phasor (S n) (KSig (S n)) (KSig (S n)) where
phasor = mkOp1 "phasor"
instance (Varable a) => Phasor (S n) (ASig (S n)) a where
phasor = mkOp1 "phasor"
instance (Varable a, Varable b, PVar out) => Oscil (S n) out a b where
oscil = mkOp3 "oscil3"
oscil' = mkOp4 "oscil3"
instance Delay (S n) where
delaySamp = mkOp1 "delay1"
vdelay3 = mkOp3 "vdelay3"
instance DelayNet (S n) where
type DelayN (S n) = SDelay n
runDelay = runDelay'
tapA = tap'
tapK = tap'
tapI = tap'
newtype SDelay n a = SDelay { unDelay :: S n a }
deriving (Functor)
instance Applicative (SDelay n) where
pure = SDelay . pure
(SDelay a) <*> (SDelay b) = SDelay (a <*> b)
runDelay' :: INum (S n) -> ASig (S n) -> SDelay n a -> S n a
runDelay' maxdel insig dl = do
tellOrc $ printf "aNull delayr %s\n" (getVarLbl maxdel)
v <- unDelay dl
tellOrc $ printf " delayw %s\n" (getVarLbl insig)
return v
tap' :: Varable b => b -> SDelay n (ASig (S n))
tap' dtime = SDelay $ mkOp1 "deltap3" dtime
t1 = do
v <- csig 1000
outs v v
t3 = do
so <- runDelay 1 1000 (tapK 1)
outs so so
all1 = mapM makeInstrument [t1,t3]
instance CsATSadd (S n) where
aTSadd = mkOp5 "aTSadd"
aTSadd' = mkOp8 "aTSadd"
instance CsATSaddnz (S n) where
aTSaddnz = mkOp3 "aTSaddnz"
aTSaddnz' = mkOp5 "aTSaddnz"
instance CsATSbufread (S n) where
aTSbufread = mkOp4 "aTSbufread"
aTSbufread' = mkOp6 "aTSbufread"
instance CsATScross (S n) where
aTScross = mkOp7 "aTScross"
aTScross' = mkOp11 "aTScross"
instance CsATSinfo (S n) where
aTSinfo = mkOp2 "aTSinfo"
instance CsATSinterpread (S n) where
aTSinterpread = mkOp1 "aTSinterpread"
instance CsATSpartialtap (S n) where
aTSpartialtap = mkOp1 "aTSpartialtap"
instance CsATSread (S n) where
aTSread = mkOp3 "aTSread"
instance CsATSreadnz (S n) where
aTSreadnz = mkOp3 "aTSreadnz"
instance CsATSsinnoi (S n) where
aTSsinnoi = mkOp6 "aTSsinnoi"
aTSsinnoi' = mkOp8 "aTSsinnoi"
instance CsMixerClear (S n) where
mixerClear = mkOp0 "mixerClear"
instance CsMixerGetLevel (S n) where
mixerGetLevel = mkOp2 "mixerGetLevel"
instance CsMixerReceive (S n) where
mixerReceive = mkOp2 "mixerReceive"
instance CsMixerSend (S n) where
mixerSend = mkOp4 "mixerSend"
instance CsMixerSetLevel (S n) where
mixerSetLevel = mkOp3 "mixerSetLevel"
instance CsMixerSetLevel_i (S n) where
mixerSetLevel_i = mkOp3 "mixerSetLevel_i"
instance CsACS (S n) where
aCS = mkOp1 "aCS"
instance (Varable a, Varable b) => CsAdd (S n) (ASig (S n)) a b where
add = mkOp2 "add"
instance CsAdd (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
add = mkOp2 "add"
instance CsAdd (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
add = mkOp2 "add"
instance (PVar out) => CsAdsr (S n) out where
adsr = mkOp4 "adsr"
adsr' = mkOp5 "adsr"
instance CsAdsyn (S n) where
adsyn = mkOp4 "adsyn"
adsyn' = mkOp5 "adsyn"
instance CsAdsynt (S n) where
adsynt = mkOp6 "adsynt"
adsynt' = mkOp7 "adsynt"
instance CsAdsynt2 (S n) where
adsynt2 = mkOp6 "adsynt2"
adsynt2' = mkOp7 "adsynt2"
instance CsAftouch (S n) where
aftouch = mkOp0 "aftouch"
aftouch' = mkOp2 "aftouch"
instance CsAlpass (S n) where
alpass = mkOp3 "alpass"
alpass' = mkOp5 "alpass"
instance CsAlwayson (S n) where
alwayson = mkOp2 "alwayson"
instance CsAmpdb (S n) (ASig (S n)) (ASig (S n)) where
ampdb = mkOp1 "ampdb"
instance CsAmpdb (S n) (KSig (S n)) (KSig (S n)) where
ampdb = mkOp1 "ampdb"
instance CsAmpdb (S n) (INum (S n)) (INum (S n)) where
ampdb = mkOp1 "ampdb"
instance CsAmpdbfs (S n) (ASig (S n)) (ASig (S n)) where
ampdbfs = mkOp1 "ampdbfs"
instance CsAmpdbfs (S n) (KSig (S n)) (KSig (S n)) where
ampdbfs = mkOp1 "ampdbfs"
instance CsAmpdbfs (S n) (INum (S n)) (INum (S n)) where
ampdbfs = mkOp1 "ampdbfs"
instance CsAmpmidi (S n) where
ampmidi = mkOp1 "ampmidi"
ampmidi' = mkOp2 "ampmidi"
instance CsAmpmidid (S n) (KSig (S n)) where
ampmidid = mkOp2 "ampmidid"
instance CsAmpmidid (S n) (INum (S n)) where
ampmidid = mkOp2 "ampmidid"
instance (Varable a, Varable b) => CsAnd (S n) (ASig (S n)) a b where
and = mkOp2 "and"
instance CsAnd (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
and = mkOp2 "and"
instance CsAnd (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
and = mkOp2 "and"
instance CsAreson (S n) where
areson = mkOp3 "areson"
areson' = mkOp5 "areson"
instance CsAresonk (S n) where
aresonk = mkOp3 "aresonk"
aresonk' = mkOp5 "aresonk"
instance CsAtone (S n) where
atone = mkOp2 "atone"
atone' = mkOp3 "atone"
instance CsAtonek (S n) where
atonek = mkOp2 "atonek"
atonek' = mkOp3 "atonek"
instance CsAtonex (S n) where
atonex = mkOp2 "atonex"
atonex' = mkOp4 "atonex"
instance CsBabo (S n) where
babo = mkOp7 "babo"
babo' = mkOp9 "babo"
instance CsBalance (S n) where
balance = mkOp2 "balance"
balance' = mkOp4 "balance"
instance CsBamboo (S n) where
bamboo = mkOp2 "bamboo"
bamboo' = mkOp8 "bamboo"
instance CsBarmodel (S n) where
barmodel = mkOp9 "barmodel"
instance CsBbcutm (S n) where
bbcutm = mkOp6 "bbcutm"
bbcutm' = mkOp9 "bbcutm"
instance CsBbcuts (S n) where
bbcuts = mkOp7 "bbcuts"
bbcuts' = mkOp10 "bbcuts"
instance CsBetarand (S n) (ASig (S n)) where
betarand = mkOp3 "betarand"
instance CsBetarand (S n) (KSig (S n)) where
betarand = mkOp3 "betarand"
instance CsBetarand (S n) (INum (S n)) where
betarand = mkOp3 "betarand"
instance CsBexprnd (S n) (ASig (S n)) where
bexprnd = mkOp1 "bexprnd"
instance CsBexprnd (S n) (KSig (S n)) where
bexprnd = mkOp1 "bexprnd"
instance CsBexprnd (S n) (INum (S n)) where
bexprnd = mkOp1 "bexprnd"
instance (Nat d) => CsBformdec (S n) d where
bformdec = mkOp5 "bformdec"
instance (Nat d) => CsBformdec1 (S n) d where
bformdec1 = mkOp2 "bformdec1"
instance (Nat d) => CsBformenc1 (S n) d where
bformenc1 = mkOp3 "bformenc1"
instance CsBinit (S n) where
binit = mkOp2 "binit"
instance CsBiquad (S n) where
biquad = mkOp7 "biquad"
biquad' = mkOp8 "biquad"
instance CsBiquada (S n) where
biquada = mkOp7 "biquada"
biquada' = mkOp8 "biquada"
instance CsBirnd (S n) (KSig (S n)) where
birnd = mkOp1 "birnd"
instance CsBirnd (S n) (INum (S n)) where
birnd = mkOp1 "birnd"
instance (Varable a, Varable b) => CsBqrez (S n) a b where
bqrez = mkOp3 "bqrez"
bqrez' = mkOp5 "bqrez"
instance CsButbp (S n) where
butbp = mkOp3 "butbp"
butbp' = mkOp4 "butbp"
instance CsButbr (S n) where
butbr = mkOp3 "butbr"
butbr' = mkOp4 "butbr"
instance CsButhp (S n) where
buthp = mkOp2 "buthp"
buthp' = mkOp3 "buthp"
instance CsButlp (S n) where
butlp = mkOp2 "butlp"
butlp' = mkOp3 "butlp"
instance CsButterbp (S n) where
butterbp = mkOp3 "butterbp"
butterbp' = mkOp4 "butterbp"
instance CsButterbr (S n) where
butterbr = mkOp3 "butterbr"
butterbr' = mkOp4 "butterbr"
instance CsButterhp (S n) where
butterhp = mkOp2 "butterhp"
butterhp' = mkOp3 "butterhp"
instance CsButterlp (S n) where
butterlp = mkOp2 "butterlp"
butterlp' = mkOp3 "butterlp"
instance CsButton (S n) where
button = mkOp1 "button"
instance (Varable a, Varable b) => CsBuzz (S n) a b where
buzz = mkOp4 "buzz"
buzz' = mkOp5 "buzz"
instance CsCabasa (S n) where
cabasa = mkOp2 "cabasa"
cabasa' = mkOp5 "cabasa"
instance CsCauchy (S n) (ASig (S n)) where
cauchy = mkOp1 "cauchy"
instance CsCauchy (S n) (KSig (S n)) where
cauchy = mkOp1 "cauchy"
instance CsCauchy (S n) (INum (S n)) where
cauchy = mkOp1 "cauchy"
instance CsCeil (S n) (ASig (S n)) (ASig (S n)) where
ceil = mkOp1 "ceil"
instance CsCeil (S n) (KSig (S n)) (KSig (S n)) where
ceil = mkOp1 "ceil"
instance CsCeil (S n) (INum (S n)) (INum (S n)) where
ceil = mkOp1 "ceil"
instance CsCent (S n) (ASig (S n)) (ASig (S n)) where
cent = mkOp1 "cent"
instance CsCent (S n) (KSig (S n)) (KSig (S n)) where
cent = mkOp1 "cent"
instance CsCent (S n) (INum (S n)) (INum (S n)) where
cent = mkOp1 "cent"
instance CsChanctrl (S n) (KSig (S n)) where
chanctrl = mkOp2 "chanctrl"
chanctrl' = mkOp4 "chanctrl"
instance CsChanctrl (S n) (INum (S n)) where
chanctrl = mkOp2 "chanctrl"
chanctrl' = mkOp4 "chanctrl"
instance CsChanged (S n) where
changed = mkOp1 "changed"
instance CsChani (S n) (ASig (S n)) where
chani = mkOp1 "chani"
instance CsChani (S n) (KSig (S n)) where
chani = mkOp1 "chani"
instance (Varable a) => CsChano (S n) a where
chano = mkOp2 "chano"
instance CsChebyshevpoly (S n) where
chebyshevpoly = mkOp2 "chebyshevpoly"
instance CsCheckbox (S n) where
checkbox = mkOp1 "checkbox"
instance CsChn_S (S n) where
chn_S = mkOp2 "chn_S"
instance CsChn_a (S n) where
chn_a = mkOp2 "chn_a"
instance CsChn_k (S n) where
chn_k = mkOp2 "chn_k"
chn_k' = mkOp6 "chn_k"
instance CsChnclear (S n) where
chnclear = mkOp1 "chnclear"
instance CsChnexport (S n) (ASig (S n)) where
chnexport = mkOp2 "chnexport"
instance CsChnexport (S n) (KSig (S n)) where
chnexport = mkOp2 "chnexport"
instance CsChnexport (S n) (INum (S n)) where
chnexport = mkOp2 "chnexport"
instance CsChnexport (S n) (VString (S n)) where
chnexport = mkOp2 "chnexport"
instance CsChnget (S n) (ASig (S n)) where
chnget = mkOp1 "chnget"
instance CsChnget (S n) (KSig (S n)) where
chnget = mkOp1 "chnget"
instance CsChnget (S n) (INum (S n)) where
chnget = mkOp1 "chnget"
instance CsChnget (S n) (VString (S n)) where
chnget = mkOp1 "chnget"
instance CsChnmix (S n) where
chnmix = mkOp2 "chnmix"
instance CsChnrecv (S n) where
chnrecv = mkOp1 "chnrecv"
chnrecv' = mkOp2 "chnrecv"
instance CsChnsend (S n) where
chnsend = mkOp1 "chnsend"
chnsend' = mkOp2 "chnsend"
instance (Varable a) => CsChnset (S n) a where
chnset = mkOp2 "chnset"
instance CsClear (S n) where
clear = mkOp1 "clear"
instance CsClfilt (S n) where
clfilt = mkOp4 "clfilt"
clfilt' = mkOp8 "clfilt"
instance CsClip (S n) where
clip = mkOp3 "clip"
clip' = mkOp4 "clip"
instance CsClockoff (S n) where
clockoff = mkOp1 "clockoff"
instance CsClockon (S n) where
clockon = mkOp1 "clockon"
instance CsComb (S n) where
comb = mkOp3 "comb"
comb' = mkOp5 "comb"
instance CsCompress (S n) where
compress = mkOp9 "compress"
instance CsConnect (S n) where
connect = mkOp4 "connect"
instance CsControl (S n) where
control = mkOp1 "control"
instance (Nat d) => CsConvle (S n) d where
convle = mkOp2 "convle"
convle' = mkOp3 "convle"
instance (Nat d) => CsConvolve (S n) d where
convolve = mkOp2 "convolve"
convolve' = mkOp3 "convolve"
instance CsCos (S n) (ASig (S n)) (ASig (S n)) where
cos = mkOp1 "cos"
instance CsCos (S n) (KSig (S n)) (KSig (S n)) where
cos = mkOp1 "cos"
instance CsCos (S n) (INum (S n)) (INum (S n)) where
cos = mkOp1 "cos"
instance CsCosh (S n) (ASig (S n)) (ASig (S n)) where
cosh = mkOp1 "cosh"
instance CsCosh (S n) (KSig (S n)) (KSig (S n)) where
cosh = mkOp1 "cosh"
instance CsCosh (S n) (INum (S n)) (INum (S n)) where
cosh = mkOp1 "cosh"
instance CsCosinv (S n) (ASig (S n)) (ASig (S n)) where
cosinv = mkOp1 "cosinv"
instance CsCosinv (S n) (KSig (S n)) (KSig (S n)) where
cosinv = mkOp1 "cosinv"
instance CsCosinv (S n) (INum (S n)) (INum (S n)) where
cosinv = mkOp1 "cosinv"
instance CsCps2pch (S n) where
cps2pch = mkOp2 "cps2pch"
instance CsCpsmidi (S n) where
cpsmidi = mkOp0 "cpsmidi"
instance CsCpsmidib (S n) (KSig (S n)) where
cpsmidib = mkOp0 "cpsmidib"
cpsmidib' = mkOp1 "cpsmidib"
instance CsCpsmidib (S n) (INum (S n)) where
cpsmidib = mkOp0 "cpsmidib"
cpsmidib' = mkOp1 "cpsmidib"
instance CsCpsmidinn (S n) (KSig (S n)) where
cpsmidinn = mkOp1 "cpsmidinn"
instance CsCpsmidinn (S n) (INum (S n)) where
cpsmidinn = mkOp1 "cpsmidinn"
instance CsCpstmid (S n) where
cpstmid = mkOp1 "cpstmid"
instance CsCpstun (S n) where
cpstun = mkOp3 "cpstun"
instance CsCpstuni (S n) where
cpstuni = mkOp2 "cpstuni"
instance CsCpsxpch (S n) where
cpsxpch = mkOp4 "cpsxpch"
instance CsCpuprc (S n) where
cpuprc = mkOp2 "cpuprc"
instance CsCross2 (S n) where
cross2 = mkOp6 "cross2"
instance (Varable a, Varable b, Varable c, Varable d) => CsCrossfm (S n) a b c d where
crossfm = mkOp7 "crossfm"
crossfm' = mkOp9 "crossfm"
instance (Varable a, Varable b, Varable c, Varable d) => CsCrossfmi (S n) a b c d where
crossfmi = mkOp7 "crossfmi"
crossfmi' = mkOp9 "crossfmi"
instance (Varable a, Varable b, Varable c, Varable d) => CsCrossfmpm (S n) a b c d where
crossfmpm = mkOp7 "crossfmpm"
crossfmpm' = mkOp9 "crossfmpm"
instance (Varable a, Varable b, Varable c, Varable d) => CsCrossfmpmi (S n) a b c d where
crossfmpmi = mkOp7 "crossfmpmi"
crossfmpmi' = mkOp9 "crossfmpmi"
instance (Varable a, Varable b, Varable c, Varable d) => CsCrosspm (S n) a b c d where
crosspm = mkOp7 "crosspm"
crosspm' = mkOp9 "crosspm"
instance (Varable a, Varable b, Varable c, Varable d) => CsCrosspmi (S n) a b c d where
crosspmi = mkOp7 "crosspmi"
crosspmi' = mkOp9 "crosspmi"
instance CsCrunch (S n) where
crunch = mkOp2 "crunch"
crunch' = mkOp5 "crunch"
instance CsCtlchn (S n) where
ctlchn = mkOp0 "ctlchn"
ctlchn' = mkOp2 "ctlchn"
instance CsCtrl14 (S n) (KSig (S n)) where
ctrl14 = mkOp5 "ctrl14"
ctrl14' = mkOp6 "ctrl14"
instance CsCtrl14 (S n) (INum (S n)) where
ctrl14 = mkOp5 "ctrl14"
ctrl14' = mkOp6 "ctrl14"
instance CsCtrl21 (S n) (KSig (S n)) where
ctrl21 = mkOp6 "ctrl21"
ctrl21' = mkOp7 "ctrl21"
instance CsCtrl21 (S n) (INum (S n)) where
ctrl21 = mkOp6 "ctrl21"
ctrl21' = mkOp7 "ctrl21"
instance CsCtrl7 (S n) (ASig (S n)) where
ctrl7 = mkOp4 "ctrl7"
ctrl7' = mkOp5 "ctrl7"
instance CsCtrl7 (S n) (KSig (S n)) where
ctrl7 = mkOp4 "ctrl7"
ctrl7' = mkOp5 "ctrl7"
instance CsCtrl7 (S n) (INum (S n)) where
ctrl7 = mkOp4 "ctrl7"
ctrl7' = mkOp5 "ctrl7"
instance CsCtrlinit (S n) where
ctrlinit = mkOp2 "ctrlinit"
instance CsCuserrnd (S n) (ASig (S n)) where
cuserrnd = mkOp3 "cuserrnd"
instance CsCuserrnd (S n) (KSig (S n)) where
cuserrnd = mkOp3 "cuserrnd"
instance CsCuserrnd (S n) (INum (S n)) where
cuserrnd = mkOp3 "cuserrnd"
instance CsDam (S n) where
dam = mkOp6 "dam"
instance CsDate (S n) where
date = mkOp0 "date"
instance CsDates (S n) where
dates = mkOp0 "dates"
dates' = mkOp1 "dates"
instance CsDb (S n) (ASig (S n)) (ASig (S n)) where
db = mkOp1 "db"
instance CsDb (S n) (KSig (S n)) (KSig (S n)) where
db = mkOp1 "db"
instance CsDb (S n) (INum (S n)) (INum (S n)) where
db = mkOp1 "db"
instance CsDbamp (S n) (KSig (S n)) where
dbamp = mkOp1 "dbamp"
instance CsDbamp (S n) (INum (S n)) where
dbamp = mkOp1 "dbamp"
instance CsDbfsamp (S n) (KSig (S n)) where
dbfsamp = mkOp1 "dbfsamp"
instance CsDbfsamp (S n) (INum (S n)) where
dbfsamp = mkOp1 "dbfsamp"
instance CsDcblock (S n) where
dcblock = mkOp1 "dcblock"
dcblock' = mkOp2 "dcblock"
instance CsDcblock2 (S n) where
dcblock2 = mkOp1 "dcblock2"
dcblock2' = mkOp3 "dcblock2"
instance CsDconv (S n) where
dconv = mkOp3 "dconv"
instance CsDelay (S n) where
delay = mkOp2 "delay"
delay' = mkOp3 "delay"
instance CsDelay1 (S n) where
delay1 = mkOp1 "delay1"
delay1' = mkOp2 "delay1"
instance CsDelayk (S n) where
delayk = mkOp2 "delayk"
delayk' = mkOp3 "delayk"
instance CsDelayw (S n) where
delayw = mkOp1 "delayw"
instance CsDeltap (S n) where
deltap = mkOp1 "deltap"
deltap' = mkOp2 "deltap"
instance (Varable a) => CsDeltap3 (S n) a where
deltap3 = mkOp1 "deltap3"
deltap3' = mkOp2 "deltap3"
instance (Varable a) => CsDeltapi (S n) a where
deltapi = mkOp1 "deltapi"
deltapi' = mkOp2 "deltapi"
instance (Varable a) => CsDeltapn (S n) a where
deltapn = mkOp1 "deltapn"
deltapn' = mkOp2 "deltapn"
instance CsDeltapx (S n) where
deltapx = mkOp2 "deltapx"
deltapx' = mkOp3 "deltapx"
instance CsDeltapxw (S n) where
deltapxw = mkOp3 "deltapxw"
deltapxw' = mkOp4 "deltapxw"
instance CsDenorm (S n) where
denorm = mkOp1 "denorm"
instance (PVar out, Varable a) => CsDiff (S n) out a where
diff = mkOp1 "diff"
diff' = mkOp2 "diff"
instance (Nat d) => CsDiskgrain (S n) d where
diskgrain = mkOp8 "diskgrain"
diskgrain' = mkOp10 "diskgrain"
instance (Nat d) => CsDiskin (S n) d where
diskin = mkOp2 "diskin"
diskin' = mkOp7 "diskin"
instance (Nat d) => CsDiskin2 (S n) d where
diskin2 = mkOp2 "diskin2"
diskin2' = mkOp8 "diskin2"
instance CsDistort (S n) where
distort = mkOp3 "distort"
distort' = mkOp5 "distort"
instance CsDistort1 (S n) where
distort1 = mkOp5 "distort1"
distort1' = mkOp6 "distort1"
instance (Varable a, Varable b) => CsDiv (S n) (ASig (S n)) a b where
div = mkOp2 "div"
instance CsDiv (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
div = mkOp2 "div"
instance CsDiv (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
div = mkOp2 "div"
instance (Varable a, Varable b) => CsDivz (S n) (ASig (S n)) a b where
divz = mkOp3 "divz"
instance CsDivz (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
divz = mkOp3 "divz"
instance CsDivz (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
divz = mkOp3 "divz"
instance CsDoppler (S n) where
doppler = mkOp3 "doppler"
doppler' = mkOp5 "doppler"
instance CsDownsamp (S n) where
downsamp = mkOp1 "downsamp"
downsamp' = mkOp2 "downsamp"
instance CsDripwater (S n) where
dripwater = mkOp2 "dripwater"
dripwater' = mkOp8 "dripwater"
instance CsDumpk (S n) where
dumpk = mkOp4 "dumpk"
instance CsDumpk2 (S n) where
dumpk2 = mkOp5 "dumpk2"
instance CsDumpk3 (S n) where
dumpk3 = mkOp6 "dumpk3"
instance CsDumpk4 (S n) where
dumpk4 = mkOp7 "dumpk4"
instance CsDuserrnd (S n) (ASig (S n)) where
duserrnd = mkOp1 "duserrnd"
instance CsDuserrnd (S n) (KSig (S n)) where
duserrnd = mkOp1 "duserrnd"
instance CsDuserrnd (S n) (INum (S n)) where
duserrnd = mkOp1 "duserrnd"
instance CsEndin (S n) where
endin = mkOp0 "endin"
instance CsEndop (S n) where
endop = mkOp0 "endop"
instance (PVar out, Varable a) => CsEnvlpx (S n) out a where
envlpx = mkOp7 "envlpx"
envlpx' = mkOp8 "envlpx"
instance (PVar out, Varable a) => CsEnvlpxr (S n) out a where
envlpxr = mkOp6 "envlpxr"
envlpxr' = mkOp8 "envlpxr"
instance (PVar out, Varable a) => CsEphasor (S n) out a where
ephasor = mkOp2 "ephasor"
ephasor' = mkOp3 "ephasor"
instance CsEqfil (S n) where
eqfil = mkOp4 "eqfil"
eqfil' = mkOp5 "eqfil"
instance CsEvent_i (S n) where
event_i = mkOp3 "event_i"
instance CsExitnow (S n) where
exitnow = mkOp0 "exitnow"
instance CsExp (S n) (ASig (S n)) (ASig (S n)) where
exp = mkOp1 "exp"
instance CsExp (S n) (KSig (S n)) (KSig (S n)) where
exp = mkOp1 "exp"
instance CsExp (S n) (INum (S n)) (INum (S n)) where
exp = mkOp1 "exp"
instance CsExpcurve (S n) where
expcurve = mkOp2 "expcurve"
instance (PVar out) => CsExpon (S n) out where
expon = mkOp3 "expon"
instance CsExprand (S n) (ASig (S n)) where
exprand = mkOp1 "exprand"
instance CsExprand (S n) (KSig (S n)) where
exprand = mkOp1 "exprand"
instance CsExprand (S n) (INum (S n)) where
exprand = mkOp1 "exprand"
instance (PVar out) => CsExpseg (S n) out where
expseg = mkOp4 "expseg"
instance CsExpsega (S n) where
expsega = mkOp4 "expsega"
instance (PVar out) => CsExpsegr (S n) out where
expsegr = mkOp4 "expsegr"
instance CsFiclose (S n) where
ficlose = mkOp1 "ficlose"
instance CsFilebit (S n) where
filebit = mkOp1 "filebit"
filebit' = mkOp2 "filebit"
instance CsFilelen (S n) where
filelen = mkOp1 "filelen"
filelen' = mkOp2 "filelen"
instance CsFilenchnls (S n) where
filenchnls = mkOp1 "filenchnls"
filenchnls' = mkOp2 "filenchnls"
instance CsFilepeak (S n) where
filepeak = mkOp1 "filepeak"
filepeak' = mkOp2 "filepeak"
instance CsFilesr (S n) where
filesr = mkOp1 "filesr"
filesr' = mkOp2 "filesr"
instance CsFilevalid (S n) where
filevalid = mkOp1 "filevalid"
instance CsFilter2 (S n) (ASig (S n)) (ASig (S n)) where
filter2 = mkOp4 "filter2"
instance CsFilter2 (S n) (KSig (S n)) (KSig (S n)) where
filter2 = mkOp4 "filter2"
instance CsFin (S n) where
fin = mkOp4 "fin"
instance CsFini (S n) where
fini = mkOp4 "fini"
instance CsFink (S n) where
fink = mkOp4 "fink"
instance CsFiopen (S n) where
fiopen = mkOp2 "fiopen"
instance CsFlanger (S n) where
flanger = mkOp3 "flanger"
flanger' = mkOp4 "flanger"
instance CsFlashtxt (S n) where
flashtxt = mkOp2 "flashtxt"
instance CsFlooper (S n) where
flooper = mkOp6 "flooper"
instance (KVar a) => CsFlooper2 (S n) a where
flooper2 = mkOp6 "flooper2"
flooper2' = mkOp11 "flooper2"
instance CsFlooper3 (S n) where
flooper3 = mkOp6 "flooper3"
flooper3' = mkOp10 "flooper3"
instance CsFmb3 (S n) where
fmb3 = mkOp11 "fmb3"
instance CsFmbell (S n) where
fmbell = mkOp11 "fmbell"
instance CsFmmetal (S n) where
fmmetal = mkOp11 "fmmetal"
instance CsFmpercfl (S n) where
fmpercfl = mkOp11 "fmpercfl"
instance CsFmrhode (S n) where
fmrhode = mkOp11 "fmrhode"
instance CsFmvoice (S n) where
fmvoice = mkOp11 "fmvoice"
instance CsFmwurlie (S n) where
fmwurlie = mkOp11 "fmwurlie"
instance (Varable a, Varable b, Varable c) => CsFof (S n) a b c where
fof = mkOp12 "fof"
fof' = mkOp15 "fof"
instance (Varable a, Varable b, Varable c) => CsFof2 (S n) a b c where
fof2 = mkOp14 "fof2"
fof2' = mkOp15 "fof2"
instance CsFofilter (S n) where
fofilter = mkOp4 "fofilter"
fofilter' = mkOp5 "fofilter"
instance (Varable a, Varable b, Varable c) => CsFog (S n) a b c where
fog = mkOp13 "fog"
fog' = mkOp16 "fog"
instance CsFold (S n) where
fold = mkOp2 "fold"
instance CsFollow (S n) where
follow = mkOp2 "follow"
instance CsFollow2 (S n) where
follow2 = mkOp3 "follow2"
instance (Varable a, Varable b, Varable c) => CsFoscil (S n) a b c where
foscil = mkOp6 "foscil"
foscil' = mkOp7 "foscil"
instance (Varable a, Varable b, Varable c) => CsFoscili (S n) a b c where
foscili = mkOp6 "foscili"
foscili' = mkOp7 "foscili"
instance CsFout (S n) where
fout = mkOp3 "fout"
instance CsFouti (S n) where
fouti = mkOp4 "fouti"
instance CsFoutir (S n) where
foutir = mkOp4 "foutir"
instance CsFoutk (S n) where
foutk = mkOp3 "foutk"
instance (Varable a) => CsFprintks (S n) a where
fprintks = mkOp3 "fprintks"
instance (Varable a) => CsFprints (S n) a where
fprints = mkOp3 "fprints"
instance CsFreeverb (S n) where
freeverb = mkOp4 "freeverb"
freeverb' = mkOp6 "freeverb"
instance CsFtchnls (S n) where
ftchnls = mkOp1 "ftchnls"
instance (Nat d) => CsFtconv (S n) d where
ftconv = mkOp3 "ftconv"
ftconv' = mkOp6 "ftconv"
instance CsFtcps (S n) where
ftcps = mkOp1 "ftcps"
instance CsFtfree (S n) where
ftfree = mkOp2 "ftfree"
instance CsFtgen (S n) where
ftgen = mkOp6 "ftgen"
instance CsFtgenonce (S n) where
ftgenonce = mkOp6 "ftgenonce"
instance CsFtgentmp (S n) where
ftgentmp = mkOp6 "ftgentmp"
instance CsFtlen (S n) where
ftlen = mkOp1 "ftlen"
instance CsFtload (S n) where
ftload = mkOp3 "ftload"
instance CsFtloadk (S n) where
ftloadk = mkOp4 "ftloadk"
instance CsFtlptim (S n) where
ftlptim = mkOp1 "ftlptim"
instance CsFtmorf (S n) where
ftmorf = mkOp3 "ftmorf"
instance CsFtsave (S n) where
ftsave = mkOp3 "ftsave"
instance CsFtsavek (S n) where
ftsavek = mkOp4 "ftsavek"
instance CsFtsr (S n) where
ftsr = mkOp1 "ftsr"
instance CsGain (S n) where
gain = mkOp2 "gain"
gain' = mkOp4 "gain"
instance CsGainslider (S n) where
gainslider = mkOp1 "gainslider"
instance CsGauss (S n) (ASig (S n)) where
gauss = mkOp1 "gauss"
instance CsGauss (S n) (KSig (S n)) where
gauss = mkOp1 "gauss"
instance CsGauss (S n) (INum (S n)) where
gauss = mkOp1 "gauss"
instance (Varable a, Varable b) => CsGbuzz (S n) a b where
gbuzz = mkOp6 "gbuzz"
gbuzz' = mkOp7 "gbuzz"
instance CsGetcfg (S n) where
getcfg = mkOp1 "getcfg"
instance CsGogobel (S n) where
gogobel = mkOp8 "gogobel"
instance (Varable a, Varable b, Varable c) => CsGrain (S n) a b c where
grain = mkOp9 "grain"
grain' = mkOp10 "grain"
instance CsGrain2 (S n) where
grain2 = mkOp6 "grain2"
grain2' = mkOp9 "grain2"
instance CsGrain3 (S n) where
grain3 = mkOp11 "grain3"
grain3' = mkOp13 "grain3"
instance (Varable a) => CsGranule (S n) a where
granule = mkOp16 "granule"
granule' = mkOp22 "granule"
instance CsGuiro (S n) where
guiro = mkOp2 "guiro"
guiro' = mkOp7 "guiro"
instance CsHarmon (S n) where
harmon = mkOp8 "harmon"
instance CsHarmon2 (S n) where
harmon2 = mkOp6 "harmon2"
harmon2' = mkOp7 "harmon2"
instance CsHarmon3 (S n) where
harmon3 = mkOp7 "harmon3"
harmon3' = mkOp8 "harmon3"
instance CsHarmon4 (S n) where
harmon4 = mkOp8 "harmon4"
harmon4' = mkOp9 "harmon4"
instance CsHilbert (S n) where
hilbert = mkOp1 "hilbert"
instance CsHrtfer (S n) where
hrtfer = mkOp4 "hrtfer"
instance CsHrtfmove (S n) where
hrtfmove = mkOp5 "hrtfmove"
hrtfmove' = mkOp8 "hrtfmove"
instance CsHrtfmove2 (S n) where
hrtfmove2 = mkOp5 "hrtfmove2"
hrtfmove2' = mkOp8 "hrtfmove2"
instance CsHrtfstat (S n) where
hrtfstat = mkOp5 "hrtfstat"
hrtfstat' = mkOp7 "hrtfstat"
instance CsHsboscil (S n) where
hsboscil = mkOp6 "hsboscil"
hsboscil' = mkOp8 "hsboscil"
instance CsHvs1 (S n) where
hvs1 = mkOp6 "hvs1"
hvs1' = mkOp7 "hvs1"
instance CsHvs2 (S n) where
hvs2 = mkOp8 "hvs2"
hvs2' = mkOp9 "hvs2"
instance CsHvs3 (S n) where
hvs3 = mkOp10 "hvs3"
hvs3' = mkOp11 "hvs3"
instance CsICS (S n) where
iCS = mkOp1 "iCS"
instance CsIhold (S n) where
ihold = mkOp0 "ihold"
instance CsInCS (S n) where
inCS = mkOp0 "inCS"
instance (Nat d) => CsInch (S n) d where
inch = mkOp1 "inch"
instance CsInitc14 (S n) where
initc14 = mkOp4 "initc14"
instance CsInitc21 (S n) where
initc21 = mkOp5 "initc21"
instance CsInitc7 (S n) where
initc7 = mkOp3 "initc7"
instance CsInleta (S n) where
inleta = mkOp1 "inleta"
instance CsInletf (S n) where
inletf = mkOp1 "inletf"
instance CsInletk (S n) where
inletk = mkOp1 "inletk"
instance CsInq (S n) where
inq = mkOp0 "inq"
instance CsInrg (S n) where
inrg = mkOp2 "inrg"
instance CsIns (S n) where
ins = mkOp0 "ins"
instance CsInsglobal (S n) where
insglobal = mkOp2 "insglobal"
instance CsInsremot (S n) where
insremot = mkOp3 "insremot"
instance CsInstr (S n) where
instr = mkOp0 "instr"
instance (PVar out, Varable a) => CsInteg (S n) out a where
integ = mkOp1 "integ"
integ' = mkOp2 "integ"
instance CsInterp (S n) where
interp = mkOp1 "interp"
interp' = mkOp3 "interp"
instance CsInvalue (S n) (KSig (S n)) where
invalue = mkOp1 "invalue"
instance CsInvalue (S n) (VString (S n)) where
invalue = mkOp1 "invalue"
instance CsInz (S n) where
inz = mkOp1 "inz"
instance CsJitter (S n) where
jitter = mkOp3 "jitter"
instance CsJitter2 (S n) where
jitter2 = mkOp7 "jitter2"
instance (PVar out, Varable a) => CsJspline (S n) out a where
jspline = mkOp3 "jspline"
instance CsKCS (S n) where
kCS = mkOp1 "kCS"
instance CsKtableseg (S n) where
ktableseg = mkOp4 "ktableseg"
instance (PVar out) => CsLfo (S n) out where
lfo = mkOp2 "lfo"
lfo' = mkOp3 "lfo"
instance (Varable a) => CsLimit (S n) (ASig (S n)) a where
limit = mkOp3 "limit"
instance (Varable a) => CsLimit (S n) (KSig (S n)) a where
limit = mkOp3 "limit"
instance CsLimit (S n) (INum (S n)) (INum (S n)) where
limit = mkOp3 "limit"
instance (PVar out) => CsLine (S n) out where
line = mkOp3 "line"
instance (PVar out, Varable a) => CsLinen (S n) out a where
linen = mkOp4 "linen"
instance (PVar out, Varable a) => CsLinenr (S n) out a where
linenr = mkOp4 "linenr"
instance CsLineto (S n) where
lineto = mkOp2 "lineto"
instance CsLinrand (S n) (ASig (S n)) where
linrand = mkOp1 "linrand"
instance CsLinrand (S n) (KSig (S n)) where
linrand = mkOp1 "linrand"
instance CsLinrand (S n) (INum (S n)) where
linrand = mkOp1 "linrand"
instance (PVar out) => CsLinseg (S n) out where
linseg = mkOp4 "linseg"
instance (PVar out) => CsLinsegr (S n) out where
linsegr = mkOp4 "linsegr"
instance (Nat d) => CsLocsend (S n) d where
locsend = mkOp0 "locsend"
instance (Nat d) => CsLocsig (S n) d where
locsig = mkOp4 "locsig"
instance CsLog (S n) (ASig (S n)) (ASig (S n)) where
log = mkOp1 "log"
instance CsLog (S n) (KSig (S n)) (KSig (S n)) where
log = mkOp1 "log"
instance CsLog (S n) (INum (S n)) (INum (S n)) where
log = mkOp1 "log"
instance CsLog10 (S n) (ASig (S n)) (ASig (S n)) where
log10 = mkOp1 "log10"
instance CsLog10 (S n) (KSig (S n)) (KSig (S n)) where
log10 = mkOp1 "log10"
instance CsLog10 (S n) (INum (S n)) (INum (S n)) where
log10 = mkOp1 "log10"
instance CsLogcurve (S n) where
logcurve = mkOp2 "logcurve"
instance CsLoopseg (S n) where
loopseg = mkOp4 "loopseg"
instance CsLoopsegp (S n) where
loopsegp = mkOp2 "loopsegp"
instance CsLooptseg (S n) where
looptseg = mkOp4 "looptseg"
instance CsLoopxseg (S n) where
loopxseg = mkOp4 "loopxseg"
instance CsLorenz (S n) where
lorenz = mkOp8 "lorenz"
lorenz' = mkOp9 "lorenz"
instance CsLorismorph (S n) where
lorismorph = mkOp6 "lorismorph"
instance CsLorisplay (S n) where
lorisplay = mkOp4 "lorisplay"
instance CsLorisread (S n) where
lorisread = mkOp6 "lorisread"
lorisread' = mkOp7 "lorisread"
instance (Nat d, Varable a) => CsLoscil (S n) d a where
loscil = mkOp3 "loscil"
loscil' = mkOp10 "loscil"
instance (Nat d, Varable a) => CsLoscil3 (S n) d a where
loscil3 = mkOp3 "loscil3"
loscil3' = mkOp10 "loscil3"
instance (Nat d, Varable a) => CsLoscilx (S n) d a where
loscilx = mkOp3 "loscilx"
loscilx' = mkOp9 "loscilx"
instance CsLowpass2 (S n) where
lowpass2 = mkOp3 "lowpass2"
lowpass2' = mkOp4 "lowpass2"
instance CsLowres (S n) where
lowres = mkOp3 "lowres"
lowres' = mkOp4 "lowres"
instance CsLowresx (S n) where
lowresx = mkOp3 "lowresx"
lowresx' = mkOp5 "lowresx"
instance CsLpf18 (S n) where
lpf18 = mkOp4 "lpf18"
instance CsLpform (S n) where
lpform = mkOp1 "lpform"
instance CsLpfreson (S n) where
lpfreson = mkOp2 "lpfreson"
instance (Varable a) => CsLphasor (S n) a where
lphasor = mkOp1 "lphasor"
lphasor' = mkOp8 "lphasor"
instance CsLpinterp (S n) where
lpinterp = mkOp3 "lpinterp"
instance CsLposcil (S n) where
lposcil = mkOp5 "lposcil"
lposcil' = mkOp6 "lposcil"
instance CsLposcil3 (S n) where
lposcil3 = mkOp5 "lposcil3"
lposcil3' = mkOp6 "lposcil3"
instance CsLposcila (S n) where
lposcila = mkOp5 "lposcila"
lposcila' = mkOp6 "lposcila"
instance CsLposcilsa (S n) where
lposcilsa = mkOp5 "lposcilsa"
lposcilsa' = mkOp6 "lposcilsa"
instance CsLposcilsa2 (S n) where
lposcilsa2 = mkOp5 "lposcilsa2"
lposcilsa2' = mkOp6 "lposcilsa2"
instance CsLpread (S n) where
lpread = mkOp2 "lpread"
lpread' = mkOp4 "lpread"
instance CsLpreson (S n) where
lpreson = mkOp1 "lpreson"
instance CsLpshold (S n) where
lpshold = mkOp4 "lpshold"
instance CsLpsholdp (S n) where
lpsholdp = mkOp2 "lpsholdp"
instance CsLpslot (S n) where
lpslot = mkOp1 "lpslot"
instance CsMac (S n) where
mac = mkOp1 "mac"
instance CsMaca (S n) where
maca = mkOp1 "maca"
instance (PVar out) => CsMadsr (S n) out where
madsr = mkOp4 "madsr"
madsr' = mkOp6 "madsr"
instance CsMandel (S n) where
mandel = mkOp4 "mandel"
instance CsMandol (S n) where
mandol = mkOp7 "mandol"
mandol' = mkOp8 "mandol"
instance CsMarimba (S n) where
marimba = mkOp9 "marimba"
marimba' = mkOp11 "marimba"
instance CsMassign (S n) where
massign = mkOp2 "massign"
massign' = mkOp3 "massign"
instance CsMax_k (S n) where
max_k = mkOp3 "max_k"
instance CsMaxabsaccum (S n) where
maxabsaccum = mkOp2 "maxabsaccum"
instance CsMaxaccum (S n) where
maxaccum = mkOp2 "maxaccum"
instance CsMaxalloc (S n) where
maxalloc = mkOp2 "maxalloc"
instance CsMaxk (S n) where
maxk = mkOp3 "maxk"
instance CsMclock (S n) where
mclock = mkOp1 "mclock"
instance CsMdelay (S n) where
mdelay = mkOp5 "mdelay"
instance CsMedian (S n) where
median = mkOp3 "median"
median' = mkOp4 "median"
instance CsMediank (S n) where
mediank = mkOp3 "mediank"
mediank' = mkOp4 "mediank"
instance CsMetro (S n) where
metro = mkOp1 "metro"
metro' = mkOp2 "metro"
instance CsMidglobal (S n) where
midglobal = mkOp2 "midglobal"
instance CsMidic14 (S n) (KSig (S n)) where
midic14 = mkOp4 "midic14"
midic14' = mkOp5 "midic14"
instance CsMidic14 (S n) (INum (S n)) where
midic14 = mkOp4 "midic14"
midic14' = mkOp5 "midic14"
instance CsMidic21 (S n) (KSig (S n)) where
midic21 = mkOp5 "midic21"
midic21' = mkOp6 "midic21"
instance CsMidic21 (S n) (INum (S n)) where
midic21 = mkOp5 "midic21"
midic21' = mkOp6 "midic21"
instance CsMidic7 (S n) (KSig (S n)) where
midic7 = mkOp3 "midic7"
midic7' = mkOp4 "midic7"
instance CsMidic7 (S n) (INum (S n)) where
midic7 = mkOp3 "midic7"
midic7' = mkOp4 "midic7"
instance (Varable a) => CsMidichannelaftertouch (S n) a where
midichannelaftertouch = mkOp1 "midichannelaftertouch"
midichannelaftertouch' = mkOp3 "midichannelaftertouch"
instance CsMidichn (S n) where
midichn = mkOp0 "midichn"
instance (Varable a, Varable b) => CsMidicontrolchange (S n) a b where
midicontrolchange = mkOp2 "midicontrolchange"
midicontrolchange' = mkOp4 "midicontrolchange"
instance CsMidictrl (S n) (KSig (S n)) where
midictrl = mkOp1 "midictrl"
midictrl' = mkOp3 "midictrl"
instance CsMidictrl (S n) (INum (S n)) where
midictrl = mkOp1 "midictrl"
midictrl' = mkOp3 "midictrl"
instance (Varable a, Varable b) => CsMididefault (S n) a b where
mididefault = mkOp2 "mididefault"
instance CsMidiin (S n) where
midiin = mkOp0 "midiin"
instance (Varable a, Varable b) => CsMidinoteoff (S n) a b where
midinoteoff = mkOp2 "midinoteoff"
instance (Varable a, Varable b) => CsMidinoteoncps (S n) a b where
midinoteoncps = mkOp2 "midinoteoncps"
instance (Varable a, Varable b) => CsMidinoteonkey (S n) a b where
midinoteonkey = mkOp2 "midinoteonkey"
instance (Varable a, Varable b) => CsMidinoteonoct (S n) a b where
midinoteonoct = mkOp2 "midinoteonoct"
instance (Varable a, Varable b) => CsMidinoteonpch (S n) a b where
midinoteonpch = mkOp2 "midinoteonpch"
instance CsMidion (S n) where
midion = mkOp3 "midion"
instance CsMidion2 (S n) where
midion2 = mkOp4 "midion2"
instance CsMidiout (S n) where
midiout = mkOp4 "midiout"
instance CsMidipgm (S n) where
midipgm = mkOp0 "midipgm"
midipgm' = mkOp1 "midipgm"
instance (Varable a) => CsMidipitchbend (S n) a where
midipitchbend = mkOp1 "midipitchbend"
midipitchbend' = mkOp3 "midipitchbend"
instance (Varable a, Varable b) => CsMidipolyaftertouch (S n) a b where
midipolyaftertouch = mkOp2 "midipolyaftertouch"
midipolyaftertouch' = mkOp4 "midipolyaftertouch"
instance (Varable a) => CsMidiprogramchange (S n) a where
midiprogramchange = mkOp1 "midiprogramchange"
instance CsMiditempo (S n) where
miditempo = mkOp0 "miditempo"
instance CsMidremot (S n) where
midremot = mkOp3 "midremot"
instance CsMinabsaccum (S n) where
minabsaccum = mkOp2 "minabsaccum"
instance CsMinaccum (S n) where
minaccum = mkOp2 "minaccum"
instance (Nat d) => CsMincer (S n) d where
mincer = mkOp5 "mincer"
mincer' = mkOp7 "mincer"
instance CsMirror (S n) (ASig (S n)) (ASig (S n)) where
mirror = mkOp3 "mirror"
instance CsMirror (S n) (KSig (S n)) (KSig (S n)) where
mirror = mkOp3 "mirror"
instance CsMirror (S n) (INum (S n)) (INum (S n)) where
mirror = mkOp3 "mirror"
instance (Varable a, Varable b) => CsMod (S n) (ASig (S n)) a b where
mod = mkOp2 "mod"
instance CsMod (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
mod = mkOp2 "mod"
instance CsMod (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
mod = mkOp2 "mod"
instance CsMode (S n) where
mode = mkOp3 "mode"
mode' = mkOp4 "mode"
instance CsModmatrix (S n) where
modmatrix = mkOp7 "modmatrix"
instance (Nat d) => CsMonitor (S n) d where
monitor = mkOp0 "monitor"
instance CsMoog (S n) where
moog = mkOp9 "moog"
instance CsMoogladder (S n) where
moogladder = mkOp3 "moogladder"
moogladder' = mkOp4 "moogladder"
instance (Varable a, Varable b) => CsMoogvcf (S n) a b where
moogvcf = mkOp3 "moogvcf"
moogvcf' = mkOp5 "moogvcf"
instance (Varable a, Varable b) => CsMoogvcf2 (S n) a b where
moogvcf2 = mkOp3 "moogvcf2"
moogvcf2' = mkOp5 "moogvcf2"
instance CsMoscil (S n) where
moscil = mkOp5 "moscil"
instance CsMpulse (S n) where
mpulse = mkOp2 "mpulse"
mpulse' = mkOp3 "mpulse"
instance CsMrtmsg (S n) where
mrtmsg = mkOp1 "mrtmsg"
instance (Varable a, Varable b) => CsMul (S n) (ASig (S n)) a b where
mul = mkOp2 "mul"
instance CsMul (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
mul = mkOp2 "mul"
instance CsMul (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
mul = mkOp2 "mul"
instance CsMultitap (S n) where
multitap = mkOp2 "multitap"
instance CsMute (S n) where
mute = mkOp1 "mute"
mute' = mkOp2 "mute"
instance CsMutex_lock (S n) where
mutex_lock = mkOp1 "mutex_lock"
instance CsMutex_locki (S n) where
mutex_locki = mkOp1 "mutex_locki"
instance CsMutex_unlock (S n) where
mutex_unlock = mkOp1 "mutex_unlock"
instance CsMutex_unlocki (S n) where
mutex_unlocki = mkOp1 "mutex_unlocki"
instance (PVar out) => CsMxadsr (S n) out where
mxadsr = mkOp4 "mxadsr"
mxadsr' = mkOp6 "mxadsr"
instance CsNestedap (S n) where
nestedap = mkOp5 "nestedap"
nestedap' = mkOp10 "nestedap"
instance CsNlalp (S n) where
nlalp = mkOp3 "nlalp"
nlalp' = mkOp5 "nlalp"
instance CsNlfilt (S n) where
nlfilt = mkOp6 "nlfilt"
instance (Varable a) => CsNoise (S n) a where
noise = mkOp2 "noise"
instance CsNot (S n) (ASig (S n)) (ASig (S n)) where
not = mkOp1 "not"
instance CsNot (S n) (KSig (S n)) (KSig (S n)) where
not = mkOp1 "not"
instance CsNot (S n) (INum (S n)) (INum (S n)) where
not = mkOp1 "not"
instance CsNoteoff (S n) where
noteoff = mkOp3 "noteoff"
instance CsNoteon (S n) where
noteon = mkOp3 "noteon"
instance CsNoteondur (S n) where
noteondur = mkOp4 "noteondur"
instance CsNoteondur2 (S n) where
noteondur2 = mkOp4 "noteondur2"
instance CsNotnum (S n) where
notnum = mkOp0 "notnum"
instance CsNreverb (S n) where
nreverb = mkOp3 "nreverb"
nreverb' = mkOp8 "nreverb"
instance CsNrpn (S n) where
nrpn = mkOp3 "nrpn"
instance CsNsamp (S n) where
nsamp = mkOp1 "nsamp"
instance CsNstrnum (S n) where
nstrnum = mkOp1 "nstrnum"
instance CsNtrpol (S n) (ASig (S n)) (ASig (S n)) (ASig (S n)) where
ntrpol = mkOp3 "ntrpol"
ntrpol' = mkOp5 "ntrpol"
instance CsNtrpol (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
ntrpol = mkOp3 "ntrpol"
ntrpol' = mkOp5 "ntrpol"
instance CsNtrpol (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
ntrpol = mkOp3 "ntrpol"
ntrpol' = mkOp5 "ntrpol"
instance CsOctave (S n) (ASig (S n)) (ASig (S n)) where
octave = mkOp1 "octave"
instance CsOctave (S n) (KSig (S n)) (KSig (S n)) where
octave = mkOp1 "octave"
instance CsOctave (S n) (INum (S n)) (INum (S n)) where
octave = mkOp1 "octave"
instance CsOctmidi (S n) where
octmidi = mkOp0 "octmidi"
instance CsOctmidib (S n) (KSig (S n)) where
octmidib = mkOp0 "octmidib"
octmidib' = mkOp1 "octmidib"
instance CsOctmidib (S n) (INum (S n)) where
octmidib = mkOp0 "octmidib"
octmidib' = mkOp1 "octmidib"
instance CsOctmidinn (S n) (KSig (S n)) where
octmidinn = mkOp1 "octmidinn"
instance CsOctmidinn (S n) (INum (S n)) where
octmidinn = mkOp1 "octmidinn"
instance CsOpcode (S n) where
opcode = mkOp0 "opcode"
instance (Varable a, Varable b) => CsOr (S n) (ASig (S n)) a b where
or = mkOp2 "or"
instance CsOr (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
or = mkOp2 "or"
instance CsOr (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
or = mkOp2 "or"
instance CsOscbnk (S n) where
oscbnk = mkOp19 "oscbnk"
oscbnk' = mkOp26 "oscbnk"
instance (Varable a, Varable b) => CSE.CsOscil (S n) (ASig (S n)) a b where
oscil = mkOp3 "oscil"
oscil' = mkOp4 "oscil"
instance (PVar out) => CSE.CsOscil (S n) out (KSig (S n)) (KSig (S n)) where
oscil = mkOp3 "oscil"
oscil' = mkOp4 "oscil"
instance CsOscil1 (S n) where
oscil1 = mkOp4 "oscil1"
instance CsOscil1i (S n) where
oscil1i = mkOp4 "oscil1i"
instance (Varable a, Varable b) => CsOscil3 (S n) (ASig (S n)) a b where
oscil3 = mkOp3 "oscil3"
oscil3' = mkOp4 "oscil3"
instance (PVar out) => CsOscil3 (S n) out (KSig (S n)) (KSig (S n)) where
oscil3 = mkOp3 "oscil3"
oscil3' = mkOp4 "oscil3"
instance (Varable a, Varable b) => CSE.CsOscili (S n) (ASig (S n)) a b where
oscili = mkOp3 "oscili"
oscili' = mkOp4 "oscili"
instance (PVar out) => CSE.CsOscili (S n) out (KSig (S n)) (KSig (S n)) where
oscili = mkOp3 "oscili"
oscili' = mkOp4 "oscili"
instance (Varable a, Varable b) => CsOscilikt (S n) (ASig (S n)) a b where
oscilikt = mkOp3 "oscilikt"
oscilikt' = mkOp5 "oscilikt"
instance (PVar out) => CsOscilikt (S n) out (KSig (S n)) (KSig (S n)) where
oscilikt = mkOp3 "oscilikt"
oscilikt' = mkOp5 "oscilikt"
instance CsOsciliktp (S n) where
osciliktp = mkOp3 "osciliktp"
osciliktp' = mkOp4 "osciliktp"
instance (Varable a, Varable b) => CsOscilikts (S n) a b where
oscilikts = mkOp5 "oscilikts"
oscilikts' = mkOp6 "oscilikts"
instance CsOsciln (S n) where
osciln = mkOp4 "osciln"
instance CsOscils (S n) where
oscils = mkOp3 "oscils"
oscils' = mkOp4 "oscils"
instance CsOscilx (S n) where
oscilx = mkOp4 "oscilx"
instance CsOut32 (S n) where
out32 = mkOp32 "out32"
instance CsOutc (S n) where
outc = mkOp1 "outc"
instance CsOutch (S n) where
outch = mkOp1 "outch"
instance CsOuth (S n) where
outh = mkOp6 "outh"
instance CsOutiat (S n) where
outiat = mkOp4 "outiat"
instance CsOutic (S n) where
outic = mkOp5 "outic"
instance CsOutic14 (S n) where
outic14 = mkOp6 "outic14"
instance CsOutipat (S n) where
outipat = mkOp5 "outipat"
instance CsOutipb (S n) where
outipb = mkOp4 "outipb"
instance CsOutipc (S n) where
outipc = mkOp4 "outipc"
instance CsOutkat (S n) where
outkat = mkOp4 "outkat"
instance CsOutkc (S n) where
outkc = mkOp5 "outkc"
instance CsOutkc14 (S n) where
outkc14 = mkOp6 "outkc14"
instance CsOutkpat (S n) where
outkpat = mkOp5 "outkpat"
instance CsOutkpb (S n) where
outkpb = mkOp4 "outkpb"
instance CsOutkpc (S n) where
outkpc = mkOp4 "outkpc"
instance CsOutleta (S n) where
outleta = mkOp2 "outleta"
instance CsOutletf (S n) where
outletf = mkOp2 "outletf"
instance CsOutletk (S n) where
outletk = mkOp2 "outletk"
instance CsOutq1 (S n) where
outq1 = mkOp1 "outq1"
instance CsOutq2 (S n) where
outq2 = mkOp1 "outq2"
instance CsOutq3 (S n) where
outq3 = mkOp1 "outq3"
instance CsOutq4 (S n) where
outq4 = mkOp1 "outq4"
instance CsOutrg (S n) where
outrg = mkOp2 "outrg"
instance CsOuts1 (S n) where
outs1 = mkOp1 "outs1"
instance CsOuts2 (S n) where
outs2 = mkOp1 "outs2"
instance CsOutx (S n) where
outx = mkOp16 "outx"
instance CsOutz (S n) where
outz = mkOp1 "outz"
instance CsP (S n) (KSig (S n)) where
p = mkOp1 "p"
instance CsP (S n) (INum (S n)) where
p = mkOp1 "p"
instance CsPan (S n) where
pan = mkOp4 "pan"
pan' = mkOp6 "pan"
instance (Varable a) => CsPan2 (S n) a where
pan2 = mkOp2 "pan2"
pan2' = mkOp3 "pan2"
instance CsPareq (S n) where
pareq = mkOp4 "pareq"
pareq' = mkOp6 "pareq"
instance CsPartials (S n) where
partials = mkOp6 "partials"
instance CsPcauchy (S n) (ASig (S n)) where
pcauchy = mkOp1 "pcauchy"
instance CsPcauchy (S n) (KSig (S n)) where
pcauchy = mkOp1 "pcauchy"
instance CsPcauchy (S n) (INum (S n)) where
pcauchy = mkOp1 "pcauchy"
instance CsPchbend (S n) (KSig (S n)) where
pchbend = mkOp0 "pchbend"
pchbend' = mkOp2 "pchbend"
instance CsPchbend (S n) (INum (S n)) where
pchbend = mkOp0 "pchbend"
pchbend' = mkOp2 "pchbend"
instance CsPchmidi (S n) where
pchmidi = mkOp0 "pchmidi"
instance CsPchmidib (S n) (KSig (S n)) where
pchmidib = mkOp0 "pchmidib"
pchmidib' = mkOp1 "pchmidib"
instance CsPchmidib (S n) (INum (S n)) where
pchmidib = mkOp0 "pchmidib"
pchmidib' = mkOp1 "pchmidib"
instance CsPchmidinn (S n) (KSig (S n)) where
pchmidinn = mkOp1 "pchmidinn"
instance CsPchmidinn (S n) (INum (S n)) where
pchmidinn = mkOp1 "pchmidinn"
instance (Nat d) => CsPconvolve (S n) d where
pconvolve = mkOp2 "pconvolve"
pconvolve' = mkOp4 "pconvolve"
instance CsPcount (S n) where
pcount = mkOp0 "pcount"
instance CsPdclip (S n) where
pdclip = mkOp3 "pdclip"
pdclip' = mkOp5 "pdclip"
instance CsPdhalf (S n) where
pdhalf = mkOp2 "pdhalf"
pdhalf' = mkOp4 "pdhalf"
instance CsPdhalfy (S n) where
pdhalfy = mkOp2 "pdhalfy"
pdhalfy' = mkOp4 "pdhalfy"
instance (Varable a) => CsPeak (S n) a where
peak = mkOp1 "peak"
instance CsPgmassign (S n) where
pgmassign = mkOp2 "pgmassign"
pgmassign' = mkOp3 "pgmassign"
instance CsPgmchn (S n) where
pgmchn = mkOp0 "pgmchn"
pgmchn' = mkOp1 "pgmchn"
instance CsPhaser1 (S n) where
phaser1 = mkOp4 "phaser1"
phaser1' = mkOp5 "phaser1"
instance CsPhaser2 (S n) where
phaser2 = mkOp7 "phaser2"
instance (PVar out, Varable a) => CsPhasorbnk (S n) out a where
phasorbnk = mkOp3 "phasorbnk"
phasorbnk' = mkOp4 "phasorbnk"
instance CsPindex (S n) where
pindex = mkOp1 "pindex"
instance (Varable a) => CsPinkish (S n) a where
pinkish = mkOp1 "pinkish"
pinkish' = mkOp5 "pinkish"
instance CsPitch (S n) where
pitch = mkOp5 "pitch"
pitch' = mkOp13 "pitch"
instance CsPitchac (S n) where
pitchac = mkOp4 "pitchac"
instance CsPitchamdf (S n) where
pitchamdf = mkOp3 "pitchamdf"
pitchamdf' = mkOp8 "pitchamdf"
instance CsPlanet (S n) where
planet = mkOp10 "planet"
planet' = mkOp12 "planet"
instance CsPluck (S n) where
pluck = mkOp5 "pluck"
pluck' = mkOp7 "pluck"
instance CsPoisson (S n) (ASig (S n)) where
poisson = mkOp1 "poisson"
instance CsPoisson (S n) (KSig (S n)) where
poisson = mkOp1 "poisson"
instance CsPoisson (S n) (INum (S n)) where
poisson = mkOp1 "poisson"
instance CsPolyaft (S n) (KSig (S n)) where
polyaft = mkOp1 "polyaft"
polyaft' = mkOp3 "polyaft"
instance CsPolyaft (S n) (INum (S n)) where
polyaft = mkOp1 "polyaft"
polyaft' = mkOp3 "polyaft"
instance CsPolynomial (S n) where
polynomial = mkOp2 "polynomial"
instance CsPop_f (S n) where
pop_f = mkOp0 "pop_f"
instance CsPort (S n) where
port = mkOp2 "port"
port' = mkOp3 "port"
instance CsPortk (S n) where
portk = mkOp2 "portk"
portk' = mkOp3 "portk"
instance (Varable a, Varable b) => CsPoscil (S n) (ASig (S n)) a b where
poscil = mkOp3 "poscil"
poscil' = mkOp4 "poscil"
instance (PVar out) => CsPoscil (S n) out (KSig (S n)) (KSig (S n)) where
poscil = mkOp3 "poscil"
poscil' = mkOp4 "poscil"
instance (PVar out) => CsPoscil3 (S n) out where
poscil3 = mkOp3 "poscil3"
poscil3' = mkOp4 "poscil3"
instance CsPow (S n) (ASig (S n)) (ASig (S n)) where
pow = mkOp2 "pow"
pow' = mkOp3 "pow"
instance CsPow (S n) (KSig (S n)) (KSig (S n)) where
pow = mkOp2 "pow"
pow' = mkOp3 "pow"
instance CsPow (S n) (INum (S n)) (INum (S n)) where
pow = mkOp2 "pow"
pow' = mkOp3 "pow"
instance CsPowershape (S n) where
powershape = mkOp2 "powershape"
powershape' = mkOp3 "powershape"
instance CsPowoftwo (S n) (ASig (S n)) (ASig (S n)) where
powoftwo = mkOp1 "powoftwo"
instance CsPowoftwo (S n) (KSig (S n)) (KSig (S n)) where
powoftwo = mkOp1 "powoftwo"
instance CsPowoftwo (S n) (INum (S n)) (INum (S n)) where
powoftwo = mkOp1 "powoftwo"
instance CsPrealloc (S n) where
prealloc = mkOp2 "prealloc"
prealloc' = mkOp3 "prealloc"
instance (Nat d) => CsPrepiano (S n) d where
prepiano = mkOp15 "prepiano"
prepiano' = mkOp17 "prepiano"
instance CsPrint (S n) where
print = mkOp1 "print"
instance CsPrintf_i (S n) where
printf_i = mkOp4 "printf_i"
instance CsPrintk (S n) where
printk = mkOp2 "printk"
printk' = mkOp3 "printk"
instance CsPrintk2 (S n) where
printk2 = mkOp1 "printk2"
printk2' = mkOp2 "printk2"
instance (Varable a) => CsPrintks (S n) a where
printks = mkOp3 "printks"
instance (Varable a) => CsPrints (S n) a where
prints = mkOp2 "prints"
instance CsProduct (S n) where
product = mkOp1 "product"
instance CsPset (S n) where
pset = mkOp1 "pset"
instance CsPtrack (S n) where
ptrack = mkOp2 "ptrack"
ptrack' = mkOp3 "ptrack"
instance CsPush (S n) where
push = mkOp1 "push"
instance CsPush_f (S n) where
push_f = mkOp1 "push_f"
instance CsPuts (S n) where
puts = mkOp2 "puts"
puts' = mkOp3 "puts"
instance CsPvadd (S n) where
pvadd = mkOp5 "pvadd"
pvadd' = mkOp10 "pvadd"
instance CsPvbufread (S n) where
pvbufread = mkOp2 "pvbufread"
instance CsPvcross (S n) where
pvcross = mkOp5 "pvcross"
pvcross' = mkOp6 "pvcross"
instance CsPvinterp (S n) where
pvinterp = mkOp9 "pvinterp"
instance CsPvoc (S n) where
pvoc = mkOp3 "pvoc"
pvoc' = mkOp7 "pvoc"
instance CsPvread (S n) where
pvread = mkOp3 "pvread"
instance CsPvsadsyn (S n) where
pvsadsyn = mkOp3 "pvsadsyn"
pvsadsyn' = mkOp6 "pvsadsyn"
instance CsPvsanal (S n) where
pvsanal = mkOp5 "pvsanal"
pvsanal' = mkOp7 "pvsanal"
instance CsPvsarp (S n) where
pvsarp = mkOp4 "pvsarp"
instance (Varable a, Varable b, Varable c, Varable d, KVar e) => CsPvsbandp (S n) a b c d e where
pvsbandp = mkOp5 "pvsbandp"
pvsbandp' = mkOp6 "pvsbandp"
instance (Varable a, Varable b, Varable c, Varable d, KVar e) => CsPvsbandr (S n) a b c d e where
pvsbandr = mkOp5 "pvsbandr"
pvsbandr' = mkOp6 "pvsbandr"
instance (PVar out) => CsPvsbin (S n) out where
pvsbin = mkOp2 "pvsbin"
instance CsPvsblur (S n) where
pvsblur = mkOp3 "pvsblur"
instance CsPvsbuffer (S n) where
pvsbuffer = mkOp2 "pvsbuffer"
instance (KVar a, KVar b) => CsPvsbufread (S n) a b where
pvsbufread = mkOp2 "pvsbufread"
pvsbufread' = mkOp5 "pvsbufread"
instance (PVar out) => CsPvscent (S n) out where
pvscent = mkOp1 "pvscent"
instance CsPvscross (S n) where
pvscross = mkOp4 "pvscross"
instance CsPvsdemix (S n) where
pvsdemix = mkOp5 "pvsdemix"
instance CsPvsdisp (S n) where
pvsdisp = mkOp1 "pvsdisp"
pvsdisp' = mkOp3 "pvsdisp"
instance (Varable a) => CsPvsfilter (S n) a where
pvsfilter = mkOp3 "pvsfilter"
pvsfilter' = mkOp4 "pvsfilter"
instance CsPvsfread (S n) where
pvsfread = mkOp2 "pvsfread"
pvsfread' = mkOp3 "pvsfread"
instance CsPvsfreeze (S n) where
pvsfreeze = mkOp3 "pvsfreeze"
instance CsPvsftr (S n) where
pvsftr = mkOp2 "pvsftr"
pvsftr' = mkOp3 "pvsftr"
instance CsPvsftw (S n) where
pvsftw = mkOp2 "pvsftw"
pvsftw' = mkOp3 "pvsftw"
instance CsPvsfwrite (S n) where
pvsfwrite = mkOp2 "pvsfwrite"
instance (Varable a, KVar b, KVar c, KVar d) => CsPvshift (S n) a b c d where
pvshift = mkOp3 "pvshift"
pvshift' = mkOp6 "pvshift"
instance CsPvsifd (S n) where
pvsifd = mkOp4 "pvsifd"
pvsifd' = mkOp5 "pvsifd"
instance CsPvsin (S n) where
pvsin = mkOp1 "pvsin"
pvsin' = mkOp6 "pvsin"
instance CsPvsinfo (S n) where
pvsinfo = mkOp1 "pvsinfo"
instance CsPvsinit (S n) where
pvsinit = mkOp1 "pvsinit"
pvsinit' = mkOp5 "pvsinit"
instance CsPvslock (S n) where
pvslock = mkOp2 "pvslock"
instance CsPvsmaska (S n) where
pvsmaska = mkOp3 "pvsmaska"
instance CsPvsmix (S n) where
pvsmix = mkOp2 "pvsmix"
instance (Varable a, Varable b) => CsPvsmooth (S n) a b where
pvsmooth = mkOp3 "pvsmooth"
instance CsPvsmorph (S n) where
pvsmorph = mkOp4 "pvsmorph"
instance CsPvsosc (S n) where
pvsosc = mkOp4 "pvsosc"
pvsosc' = mkOp8 "pvsosc"
instance CsPvsout (S n) where
pvsout = mkOp2 "pvsout"
instance CsPvspitch (S n) where
pvspitch = mkOp2 "pvspitch"
instance CsPvstencil (S n) where
pvstencil = mkOp4 "pvstencil"
instance (KVar a) => CsPvsvoc (S n) a where
pvsvoc = mkOp4 "pvsvoc"
pvsvoc' = mkOp5 "pvsvoc"
instance CsPvsynth (S n) where
pvsynth = mkOp1 "pvsynth"
pvsynth' = mkOp2 "pvsynth"
instance (PVar out, Varable a) => CsRand (S n) out a where
rand = mkOp1 "rand"
rand' = mkOp4 "rand"
instance (PVar out, Varable a, Varable b) => CsRandh (S n) out a b where
randh = mkOp2 "randh"
randh' = mkOp5 "randh"
instance (PVar out, Varable a, Varable b) => CsRandi (S n) out a b where
randi = mkOp2 "randi"
randi' = mkOp5 "randi"
instance CsRandom (S n) (ASig (S n)) where
random = mkOp2 "random"
instance CsRandom (S n) (KSig (S n)) where
random = mkOp2 "random"
instance CsRandom (S n) (INum (S n)) where
random = mkOp2 "random"
instance (PVar out, Varable a) => CsRandomh (S n) out a where
randomh = mkOp3 "randomh"
instance (PVar out, Varable a) => CsRandomi (S n) out a where
randomi = mkOp3 "randomi"
instance CsRbjeq (S n) where
rbjeq = mkOp5 "rbjeq"
rbjeq' = mkOp6 "rbjeq"
instance CsReadclock (S n) where
readclock = mkOp1 "readclock"
instance CsReadk (S n) where
readk = mkOp3 "readk"
instance CsReadk2 (S n) where
readk2 = mkOp3 "readk2"
instance CsReadk3 (S n) where
readk3 = mkOp3 "readk3"
instance CsReadk4 (S n) where
readk4 = mkOp3 "readk4"
instance CsReadks (S n) where
readks = mkOp2 "readks"
instance CsRelease (S n) where
release = mkOp0 "release"
instance CsRemoteport (S n) where
remoteport = mkOp1 "remoteport"
instance CsRemove (S n) where
remove = mkOp1 "remove"
instance CsRepluck (S n) where
repluck = mkOp6 "repluck"
instance CsReson (S n) where
reson = mkOp3 "reson"
reson' = mkOp5 "reson"
instance CsResonk (S n) where
resonk = mkOp3 "resonk"
resonk' = mkOp5 "resonk"
instance CsResonr (S n) where
resonr = mkOp3 "resonr"
resonr' = mkOp5 "resonr"
instance CsResonx (S n) where
resonx = mkOp3 "resonx"
resonx' = mkOp6 "resonx"
instance CsResonxk (S n) where
resonxk = mkOp3 "resonxk"
resonxk' = mkOp6 "resonxk"
instance CsResony (S n) where
resony = mkOp5 "resony"
resony' = mkOp8 "resony"
instance CsResonz (S n) where
resonz = mkOp3 "resonz"
resonz' = mkOp5 "resonz"
instance CsResyn (S n) where
resyn = mkOp5 "resyn"
instance CsReverb (S n) where
reverb = mkOp2 "reverb"
reverb' = mkOp3 "reverb"
instance CsReverb2 (S n) where
reverb2 = mkOp3 "reverb2"
reverb2' = mkOp8 "reverb2"
instance CsReverbsc (S n) where
reverbsc = mkOp4 "reverbsc"
reverbsc' = mkOp7 "reverbsc"
instance CsRewindscore (S n) where
rewindscore = mkOp0 "rewindscore"
instance (Varable a, Varable b) => CsRezzy (S n) a b where
rezzy = mkOp3 "rezzy"
rezzy' = mkOp5 "rezzy"
instance CsRireturn (S n) where
rireturn = mkOp0 "rireturn"
instance CsRms (S n) where
rms = mkOp1 "rms"
rms' = mkOp3 "rms"
instance CsRnd (S n) (KSig (S n)) where
rnd = mkOp1 "rnd"
instance CsRnd (S n) (INum (S n)) where
rnd = mkOp1 "rnd"
instance CsRnd31 (S n) (ASig (S n)) where
rnd31 = mkOp2 "rnd31"
rnd31' = mkOp3 "rnd31"
instance CsRnd31 (S n) (KSig (S n)) where
rnd31 = mkOp2 "rnd31"
rnd31' = mkOp3 "rnd31"
instance CsRnd31 (S n) (INum (S n)) where
rnd31 = mkOp2 "rnd31"
rnd31' = mkOp3 "rnd31"
instance CsRound (S n) (ASig (S n)) (ASig (S n)) where
round = mkOp1 "round"
instance CsRound (S n) (KSig (S n)) (KSig (S n)) where
round = mkOp1 "round"
instance CsRound (S n) (INum (S n)) (INum (S n)) where
round = mkOp1 "round"
instance (PVar out, Varable a, Varable b) => CsRspline (S n) out a b where
rspline = mkOp4 "rspline"
instance CsRtclock (S n) (KSig (S n)) where
rtclock = mkOp0 "rtclock"
instance CsRtclock (S n) (INum (S n)) where
rtclock = mkOp0 "rtclock"
instance (PVar out, Varable a, Varable b) => CsSamphold (S n) out a b where
samphold = mkOp2 "samphold"
samphold' = mkOp4 "samphold"
instance CsSandpaper (S n) where
sandpaper = mkOp2 "sandpaper"
sandpaper' = mkOp5 "sandpaper"
instance CsScale (S n) where
scale = mkOp3 "scale"
instance CsScanhammer (S n) where
scanhammer = mkOp4 "scanhammer"
instance CsScans (S n) where
scans = mkOp4 "scans"
scans' = mkOp5 "scans"
instance CsScantable (S n) where
scantable = mkOp7 "scantable"
instance CsScanu (S n) where
scanu = mkOp18 "scanu"
instance CsSchedule (S n) where
schedule = mkOp4 "schedule"
instance CsSchedwhen (S n) where
schedwhen = mkOp5 "schedwhen"
instance CsScoreline (S n) where
scoreline = mkOp2 "scoreline"
instance CsScoreline_i (S n) where
scoreline_i = mkOp1 "scoreline_i"
instance CsSeed (S n) where
seed = mkOp1 "seed"
instance CsSekere (S n) where
sekere = mkOp2 "sekere"
sekere' = mkOp5 "sekere"
instance CsSemitone (S n) (ASig (S n)) (ASig (S n)) where
semitone = mkOp1 "semitone"
instance CsSemitone (S n) (KSig (S n)) (KSig (S n)) where
semitone = mkOp1 "semitone"
instance CsSemitone (S n) (INum (S n)) (INum (S n)) where
semitone = mkOp1 "semitone"
instance CsSeqtime (S n) where
seqtime = mkOp5 "seqtime"
instance CsSeqtime2 (S n) where
seqtime2 = mkOp6 "seqtime2"
instance CsSetctrl (S n) where
setctrl = mkOp3 "setctrl"
instance CsSetksmps (S n) where
setksmps = mkOp1 "setksmps"
instance CsSetscorepos (S n) where
setscorepos = mkOp1 "setscorepos"
instance CsSfilist (S n) where
sfilist = mkOp1 "sfilist"
instance (Varable a, Varable b) => CsSfinstr (S n) a b where
sfinstr = mkOp6 "sfinstr"
sfinstr' = mkOp9 "sfinstr"
instance (Varable a, Varable b) => CsSfinstr3 (S n) a b where
sfinstr3 = mkOp6 "sfinstr3"
sfinstr3' = mkOp9 "sfinstr3"
instance (Varable a, Varable b) => CsSfinstr3m (S n) a b where
sfinstr3m = mkOp6 "sfinstr3m"
sfinstr3m' = mkOp9 "sfinstr3m"
instance (Varable a, Varable b) => CsSfinstrm (S n) a b where
sfinstrm = mkOp6 "sfinstrm"
sfinstrm' = mkOp9 "sfinstrm"
instance CsSfload (S n) where
sfload = mkOp1 "sfload"
instance CsSflooper (S n) where
sflooper = mkOp8 "sflooper"
sflooper' = mkOp12 "sflooper"
instance CsSfpassign (S n) where
sfpassign = mkOp2 "sfpassign"
sfpassign' = mkOp3 "sfpassign"
instance (Varable a, Varable b) => CsSfplay (S n) a b where
sfplay = mkOp5 "sfplay"
sfplay' = mkOp8 "sfplay"
instance (Varable a, Varable b) => CsSfplay3 (S n) a b where
sfplay3 = mkOp5 "sfplay3"
sfplay3' = mkOp8 "sfplay3"
instance (Varable a, Varable b) => CsSfplay3m (S n) a b where
sfplay3m = mkOp5 "sfplay3m"
sfplay3m' = mkOp8 "sfplay3m"
instance (Varable a, Varable b) => CsSfplaym (S n) a b where
sfplaym = mkOp5 "sfplaym"
sfplaym' = mkOp8 "sfplaym"
instance CsSfplist (S n) where
sfplist = mkOp1 "sfplist"
instance CsSfpreset (S n) where
sfpreset = mkOp4 "sfpreset"
instance CsShaker (S n) where
shaker = mkOp5 "shaker"
shaker' = mkOp6 "shaker"
instance (Varable a, Varable b) => CsShl (S n) (ASig (S n)) a b where
shl = mkOp2 "shl"
instance CsShl (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
shl = mkOp2 "shl"
instance CsShl (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
shl = mkOp2 "shl"
instance (Varable a, Varable b) => CsShr (S n) (ASig (S n)) a b where
shr = mkOp2 "shr"
instance CsShr (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
shr = mkOp2 "shr"
instance CsShr (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
shr = mkOp2 "shr"
instance CsSin (S n) (ASig (S n)) (ASig (S n)) where
sin = mkOp1 "sin"
instance CsSin (S n) (KSig (S n)) (KSig (S n)) where
sin = mkOp1 "sin"
instance CsSin (S n) (INum (S n)) (INum (S n)) where
sin = mkOp1 "sin"
instance CsSinh (S n) (ASig (S n)) (ASig (S n)) where
sinh = mkOp1 "sinh"
instance CsSinh (S n) (KSig (S n)) (KSig (S n)) where
sinh = mkOp1 "sinh"
instance CsSinh (S n) (INum (S n)) (INum (S n)) where
sinh = mkOp1 "sinh"
instance CsSininv (S n) (ASig (S n)) (ASig (S n)) where
sininv = mkOp1 "sininv"
instance CsSininv (S n) (KSig (S n)) (KSig (S n)) where
sininv = mkOp1 "sininv"
instance CsSininv (S n) (INum (S n)) (INum (S n)) where
sininv = mkOp1 "sininv"
instance CsSinsyn (S n) where
sinsyn = mkOp4 "sinsyn"
instance CsSleighbells (S n) where
sleighbells = mkOp2 "sleighbells"
sleighbells' = mkOp8 "sleighbells"
instance CsSlider16table (S n) where
slider16table = mkOp83 "slider16table"
instance CsSlider16tablef (S n) where
slider16tablef = mkOp99 "slider16tablef"
instance CsSlider8table (S n) where
slider8table = mkOp43 "slider8table"
instance CsSlider8tablef (S n) where
slider8tablef = mkOp51 "slider8tablef"
instance CsSndload (S n) where
sndload = mkOp1 "sndload"
sndload' = mkOp10 "sndload"
instance CsSndloop (S n) where
sndloop = mkOp5 "sndloop"
instance (Nat d, Varable a, Varable b, Varable c) => CsSndwarp (S n) d a b c where
sndwarp = mkOp10 "sndwarp"
instance (Nat d, Varable a, Varable b, Varable c) => CsSndwarpst (S n) d a b c where
sndwarpst = mkOp10 "sndwarpst"
instance CsSockrecv (S n) where
sockrecv = mkOp2 "sockrecv"
instance CsSockrecvs (S n) where
sockrecvs = mkOp2 "sockrecvs"
instance CsSocksend (S n) where
socksend = mkOp4 "socksend"
instance CsSocksends (S n) where
socksends = mkOp5 "socksends"
instance (Nat d) => CsSoundin (S n) d where
soundin = mkOp1 "soundin"
soundin' = mkOp5 "soundin"
instance CsSoundout (S n) where
soundout = mkOp2 "soundout"
soundout' = mkOp3 "soundout"
instance CsSoundouts (S n) where
soundouts = mkOp3 "soundouts"
soundouts' = mkOp4 "soundouts"
instance CsSpace (S n) where
space = mkOp6 "space"
instance CsSpat3d (S n) where
spat3d = mkOp9 "spat3d"
spat3d' = mkOp10 "spat3d"
instance CsSpat3di (S n) where
spat3di = mkOp7 "spat3di"
spat3di' = mkOp8 "spat3di"
instance CsSpat3dt (S n) where
spat3dt = mkOp8 "spat3dt"
spat3dt' = mkOp9 "spat3dt"
instance CsSpdist (S n) where
spdist = mkOp4 "spdist"
instance CsSplitrig (S n) where
splitrig = mkOp5 "splitrig"
instance CsSprintf (S n) where
sprintf = mkOp3 "sprintf"
instance CsSpsend (S n) where
spsend = mkOp0 "spsend"
instance CsStack (S n) where
stack = mkOp1 "stack"
instance CsStatevar (S n) where
statevar = mkOp3 "statevar"
statevar' = mkOp5 "statevar"
instance CsStix (S n) where
stix = mkOp2 "stix"
stix' = mkOp5 "stix"
instance CsStrcat (S n) where
strcat = mkOp2 "strcat"
instance CsStrcatk (S n) where
strcatk = mkOp2 "strcatk"
instance CsStrchar (S n) where
strchar = mkOp1 "strchar"
strchar' = mkOp2 "strchar"
instance (KVar a) => CsStrchark (S n) a where
strchark = mkOp1 "strchark"
strchark' = mkOp2 "strchark"
instance CsStrcmp (S n) where
strcmp = mkOp2 "strcmp"
instance CsStrcmpk (S n) where
strcmpk = mkOp2 "strcmpk"
instance CsStrcpy (S n) where
strcpy = mkOp1 "strcpy"
instance CsStrcpyk (S n) where
strcpyk = mkOp1 "strcpyk"
instance CsStrecv (S n) where
strecv = mkOp2 "strecv"
instance CsStreson (S n) where
streson = mkOp3 "streson"
instance CsStrget (S n) where
strget = mkOp1 "strget"
instance CsStrindex (S n) where
strindex = mkOp2 "strindex"
instance CsStrindexk (S n) where
strindexk = mkOp2 "strindexk"
instance CsStrlen (S n) where
strlen = mkOp1 "strlen"
instance CsStrlenk (S n) where
strlenk = mkOp1 "strlenk"
instance CsStrlower (S n) where
strlower = mkOp1 "strlower"
instance CsStrlowerk (S n) where
strlowerk = mkOp1 "strlowerk"
instance CsStrrindex (S n) where
strrindex = mkOp2 "strrindex"
instance CsStrrindexk (S n) where
strrindexk = mkOp2 "strrindexk"
instance CsStrset (S n) where
strset = mkOp2 "strset"
instance CsStrsub (S n) where
strsub = mkOp1 "strsub"
strsub' = mkOp3 "strsub"
instance CsStrsubk (S n) where
strsubk = mkOp3 "strsubk"
instance CsStrtod (S n) where
strtod = mkOp1 "strtod"
instance CsStrtol (S n) where
strtol = mkOp1 "strtol"
instance CsStrupper (S n) where
strupper = mkOp1 "strupper"
instance CsStrupperk (S n) where
strupperk = mkOp1 "strupperk"
instance CsStsend (S n) where
stsend = mkOp3 "stsend"
instance (Varable a, Varable b) => CsSub (S n) (ASig (S n)) a b where
sub = mkOp2 "sub"
instance CsSub (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
sub = mkOp2 "sub"
instance CsSub (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
sub = mkOp2 "sub"
instance (Nat d) => CsSubinstr (S n) d where
subinstr = mkOp2 "subinstr"
instance CsSubinstrinit (S n) where
subinstrinit = mkOp2 "subinstrinit"
instance CSE.CsSum (S n) where
sum = mkOp1 "sum"
instance CsSvfilter (S n) where
svfilter = mkOp3 "svfilter"
svfilter' = mkOp4 "svfilter"
instance CsSyncgrain (S n) where
syncgrain = mkOp8 "syncgrain"
instance CsSyncloop (S n) where
syncloop = mkOp10 "syncloop"
syncloop' = mkOp12 "syncloop"
instance (Varable a) => CsSyncphasor (S n) a where
syncphasor = mkOp2 "syncphasor"
syncphasor' = mkOp3 "syncphasor"
instance (KVar a) => CsSystem (S n) a where
system = mkOp2 "system"
system' = mkOp3 "system"
instance CsSystem_i (S n) where
system_i = mkOp2 "system_i"
system_i' = mkOp3 "system_i"
instance (PVar out, Varable a) => CsTab (S n) out a where
tab = mkOp2 "tab"
tab' = mkOp3 "tab"
instance CsTab_i (S n) where
tab_i = mkOp2 "tab_i"
tab_i' = mkOp3 "tab_i"
instance (Varable a) => CsTable (S n) (ASig (S n)) a where
table = mkOp2 "table"
table' = mkOp5 "table"
instance (Varable a) => CsTable (S n) (KSig (S n)) a where
table = mkOp2 "table"
table' = mkOp5 "table"
instance CsTable (S n) (INum (S n)) (INum (S n)) where
table = mkOp2 "table"
table' = mkOp5 "table"
instance (Varable a) => CsTable3 (S n) (ASig (S n)) a where
table3 = mkOp2 "table3"
table3' = mkOp5 "table3"
instance (Varable a) => CsTable3 (S n) (KSig (S n)) a where
table3 = mkOp2 "table3"
table3' = mkOp5 "table3"
instance CsTable3 (S n) (INum (S n)) (INum (S n)) where
table3 = mkOp2 "table3"
table3' = mkOp5 "table3"
instance CsTablecopy (S n) where
tablecopy = mkOp2 "tablecopy"
instance CsTablegpw (S n) where
tablegpw = mkOp1 "tablegpw"
instance (Varable a) => CsTablei (S n) (ASig (S n)) a where
tablei = mkOp2 "tablei"
tablei' = mkOp5 "tablei"
instance (Varable a) => CsTablei (S n) (KSig (S n)) a where
tablei = mkOp2 "tablei"
tablei' = mkOp5 "tablei"
instance CsTablei (S n) (INum (S n)) (INum (S n)) where
tablei = mkOp2 "tablei"
tablei' = mkOp5 "tablei"
instance CsTableicopy (S n) where
tableicopy = mkOp2 "tableicopy"
instance CsTableigpw (S n) where
tableigpw = mkOp1 "tableigpw"
instance (PVar out, Varable a) => CsTableikt (S n) out a where
tableikt = mkOp2 "tableikt"
tableikt' = mkOp5 "tableikt"
instance CsTableimix (S n) where
tableimix = mkOp9 "tableimix"
instance CsTableiw (S n) where
tableiw = mkOp3 "tableiw"
tableiw' = mkOp6 "tableiw"
instance (PVar out, Varable a) => CsTablekt (S n) out a where
tablekt = mkOp2 "tablekt"
tablekt' = mkOp5 "tablekt"
instance CsTablemix (S n) where
tablemix = mkOp9 "tablemix"
instance CsTableng (S n) (KSig (S n)) where
tableng = mkOp1 "tableng"
instance CsTableng (S n) (INum (S n)) where
tableng = mkOp1 "tableng"
instance CsTablera (S n) where
tablera = mkOp3 "tablera"
instance CsTableseg (S n) where
tableseg = mkOp4 "tableseg"
instance (Varable a, Varable b) => CsTablew (S n) a b where
tablew = mkOp3 "tablew"
tablew' = mkOp6 "tablew"
instance CsTablewa (S n) where
tablewa = mkOp3 "tablewa"
instance (Varable a, Varable b) => CsTablewkt (S n) a b where
tablewkt = mkOp3 "tablewkt"
tablewkt' = mkOp6 "tablewkt"
instance (Varable a) => CsTablexkt (S n) a where
tablexkt = mkOp4 "tablexkt"
tablexkt' = mkOp7 "tablexkt"
instance CsTablexseg (S n) where
tablexseg = mkOp4 "tablexseg"
instance CsTabmorph (S n) where
tabmorph = mkOp5 "tabmorph"
instance CsTabmorpha (S n) where
tabmorpha = mkOp5 "tabmorpha"
instance CsTabmorphak (S n) where
tabmorphak = mkOp5 "tabmorphak"
instance CsTabmorphi (S n) where
tabmorphi = mkOp5 "tabmorphi"
instance CsTabplay (S n) where
tabplay = mkOp4 "tabplay"
instance CsTabrec (S n) where
tabrec = mkOp5 "tabrec"
instance (KVar a, KVar b) => CsTabsum (S n) a b where
tabsum = mkOp1 "tabsum"
tabsum' = mkOp3 "tabsum"
instance (Varable a, Varable b) => CsTabw (S n) a b where
tabw = mkOp3 "tabw"
tabw' = mkOp4 "tabw"
instance CsTabw_i (S n) where
tabw_i = mkOp3 "tabw_i"
tabw_i' = mkOp4 "tabw_i"
instance CsTambourine (S n) where
tambourine = mkOp2 "tambourine"
tambourine' = mkOp8 "tambourine"
instance CsTan (S n) (ASig (S n)) (ASig (S n)) where
tan = mkOp1 "tan"
instance CsTan (S n) (KSig (S n)) (KSig (S n)) where
tan = mkOp1 "tan"
instance CsTan (S n) (INum (S n)) (INum (S n)) where
tan = mkOp1 "tan"
instance CsTanh (S n) (ASig (S n)) (ASig (S n)) where
tanh = mkOp1 "tanh"
instance CsTanh (S n) (KSig (S n)) (KSig (S n)) where
tanh = mkOp1 "tanh"
instance CsTanh (S n) (INum (S n)) (INum (S n)) where
tanh = mkOp1 "tanh"
instance CsTaninv (S n) (ASig (S n)) (ASig (S n)) where
taninv = mkOp1 "taninv"
instance CsTaninv (S n) (KSig (S n)) (KSig (S n)) where
taninv = mkOp1 "taninv"
instance CsTaninv (S n) (INum (S n)) (INum (S n)) where
taninv = mkOp1 "taninv"
instance CsTaninv2 (S n) (ASig (S n)) (ASig (S n)) (ASig (S n)) where
taninv2 = mkOp2 "taninv2"
instance CsTaninv2 (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
taninv2 = mkOp2 "taninv2"
instance CsTaninv2 (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
taninv2 = mkOp2 "taninv2"
instance CsTb0 (S n) (KSig (S n)) where
tb0 = mkOp1 "tb0"
instance CsTb0 (S n) (INum (S n)) where
tb0 = mkOp1 "tb0"
instance CsTb0_init (S n) where
tb0_init = mkOp1 "tb0_init"
instance CsTb1 (S n) (KSig (S n)) where
tb1 = mkOp1 "tb1"
instance CsTb1 (S n) (INum (S n)) where
tb1 = mkOp1 "tb1"
instance CsTb10 (S n) (KSig (S n)) where
tb10 = mkOp1 "tb10"
instance CsTb10 (S n) (INum (S n)) where
tb10 = mkOp1 "tb10"
instance CsTb10_init (S n) where
tb10_init = mkOp1 "tb10_init"
instance CsTb11 (S n) (KSig (S n)) where
tb11 = mkOp1 "tb11"
instance CsTb11 (S n) (INum (S n)) where
tb11 = mkOp1 "tb11"
instance CsTb11_init (S n) where
tb11_init = mkOp1 "tb11_init"
instance CsTb12 (S n) (KSig (S n)) where
tb12 = mkOp1 "tb12"
instance CsTb12 (S n) (INum (S n)) where
tb12 = mkOp1 "tb12"
instance CsTb12_init (S n) where
tb12_init = mkOp1 "tb12_init"
instance CsTb13 (S n) (KSig (S n)) where
tb13 = mkOp1 "tb13"
instance CsTb13 (S n) (INum (S n)) where
tb13 = mkOp1 "tb13"
instance CsTb13_init (S n) where
tb13_init = mkOp1 "tb13_init"
instance CsTb14 (S n) (KSig (S n)) where
tb14 = mkOp1 "tb14"
instance CsTb14 (S n) (INum (S n)) where
tb14 = mkOp1 "tb14"
instance CsTb14_init (S n) where
tb14_init = mkOp1 "tb14_init"
instance CsTb15 (S n) (KSig (S n)) where
tb15 = mkOp1 "tb15"
instance CsTb15 (S n) (INum (S n)) where
tb15 = mkOp1 "tb15"
instance CsTb15_init (S n) where
tb15_init = mkOp1 "tb15_init"
instance CsTb1_init (S n) where
tb1_init = mkOp1 "tb1_init"
instance CsTb2 (S n) (KSig (S n)) where
tb2 = mkOp1 "tb2"
instance CsTb2 (S n) (INum (S n)) where
tb2 = mkOp1 "tb2"
instance CsTb2_init (S n) where
tb2_init = mkOp1 "tb2_init"
instance CsTb3 (S n) (KSig (S n)) where
tb3 = mkOp1 "tb3"
instance CsTb3 (S n) (INum (S n)) where
tb3 = mkOp1 "tb3"
instance CsTb3_init (S n) where
tb3_init = mkOp1 "tb3_init"
instance CsTb4 (S n) (KSig (S n)) where
tb4 = mkOp1 "tb4"
instance CsTb4 (S n) (INum (S n)) where
tb4 = mkOp1 "tb4"
instance CsTb4_init (S n) where
tb4_init = mkOp1 "tb4_init"
instance CsTb5 (S n) (KSig (S n)) where
tb5 = mkOp1 "tb5"
instance CsTb5 (S n) (INum (S n)) where
tb5 = mkOp1 "tb5"
instance CsTb5_init (S n) where
tb5_init = mkOp1 "tb5_init"
instance CsTb6 (S n) (KSig (S n)) where
tb6 = mkOp1 "tb6"
instance CsTb6 (S n) (INum (S n)) where
tb6 = mkOp1 "tb6"
instance CsTb6_init (S n) where
tb6_init = mkOp1 "tb6_init"
instance CsTb7 (S n) (KSig (S n)) where
tb7 = mkOp1 "tb7"
instance CsTb7 (S n) (INum (S n)) where
tb7 = mkOp1 "tb7"
instance CsTb7_init (S n) where
tb7_init = mkOp1 "tb7_init"
instance CsTb8 (S n) (KSig (S n)) where
tb8 = mkOp1 "tb8"
instance CsTb8 (S n) (INum (S n)) where
tb8 = mkOp1 "tb8"
instance CsTb8_init (S n) where
tb8_init = mkOp1 "tb8_init"
instance CsTb9 (S n) (KSig (S n)) where
tb9 = mkOp1 "tb9"
instance CsTb9 (S n) (INum (S n)) where
tb9 = mkOp1 "tb9"
instance CsTb9_init (S n) where
tb9_init = mkOp1 "tb9_init"
instance (Varable a, Varable b) => CsTbvcf (S n) a b where
tbvcf = mkOp5 "tbvcf"
tbvcf' = mkOp6 "tbvcf"
instance CsTempest (S n) where
tempest = mkOp10 "tempest"
tempest' = mkOp12 "tempest"
instance CsTempo (S n) where
tempo = mkOp2 "tempo"
instance CsTempoval (S n) where
tempoval = mkOp0 "tempoval"
instance CsTimedseq (S n) where
timedseq = mkOp3 "timedseq"
instance CsTimeinstk (S n) where
timeinstk = mkOp0 "timeinstk"
instance CsTimeinsts (S n) where
timeinsts = mkOp0 "timeinsts"
instance CsTimek (S n) (KSig (S n)) where
timek = mkOp0 "timek"
instance CsTimek (S n) (INum (S n)) where
timek = mkOp0 "timek"
instance CsTimes (S n) (KSig (S n)) where
times = mkOp0 "times"
instance CsTimes (S n) (INum (S n)) where
times = mkOp0 "times"
instance CsTival (S n) where
tival = mkOp0 "tival"
instance CsTlineto (S n) where
tlineto = mkOp3 "tlineto"
instance CsTone (S n) where
tone = mkOp2 "tone"
tone' = mkOp3 "tone"
instance CsTonek (S n) where
tonek = mkOp2 "tonek"
tonek' = mkOp3 "tonek"
instance CsTonex (S n) where
tonex = mkOp2 "tonex"
tonex' = mkOp4 "tonex"
instance CsTradsyn (S n) where
tradsyn = mkOp5 "tradsyn"
instance CsTrandom (S n) where
trandom = mkOp3 "trandom"
instance (PVar out) => CsTranseg (S n) out where
transeg = mkOp4 "transeg"
instance (PVar out) => CsTransegr (S n) out where
transegr = mkOp4 "transegr"
instance CsTrcross (S n) where
trcross = mkOp4 "trcross"
instance CsTrfilter (S n) where
trfilter = mkOp3 "trfilter"
instance CsTrigger (S n) where
trigger = mkOp3 "trigger"
instance CsTrigseq (S n) where
trigseq = mkOp6 "trigseq"
instance CsTrirand (S n) (ASig (S n)) where
trirand = mkOp1 "trirand"
instance CsTrirand (S n) (KSig (S n)) where
trirand = mkOp1 "trirand"
instance CsTrirand (S n) (INum (S n)) where
trirand = mkOp1 "trirand"
instance CsTrmix (S n) where
trmix = mkOp2 "trmix"
instance CsTrscale (S n) where
trscale = mkOp2 "trscale"
instance CsTrshift (S n) where
trshift = mkOp2 "trshift"
instance CsTrsplit (S n) where
trsplit = mkOp2 "trsplit"
instance CsTurnoff (S n) where
turnoff = mkOp0 "turnoff"
instance CsTurnoff2 (S n) where
turnoff2 = mkOp3 "turnoff2"
instance CsTurnon (S n) where
turnon = mkOp1 "turnon"
turnon' = mkOp2 "turnon"
instance CsUnirand (S n) (ASig (S n)) where
unirand = mkOp1 "unirand"
instance CsUnirand (S n) (KSig (S n)) where
unirand = mkOp1 "unirand"
instance CsUnirand (S n) (INum (S n)) where
unirand = mkOp1 "unirand"
instance CsUpsamp (S n) where
upsamp = mkOp1 "upsamp"
instance CsUrd (S n) (ASig (S n)) where
urd = mkOp1 "urd"
instance CsUrd (S n) (KSig (S n)) where
urd = mkOp1 "urd"
instance CsUrd (S n) (INum (S n)) where
urd = mkOp1 "urd"
instance (KVar a, KVar b) => CsVadd (S n) a b where
vadd = mkOp3 "vadd"
vadd' = mkOp5 "vadd"
instance CsVadd_i (S n) where
vadd_i = mkOp3 "vadd_i"
vadd_i' = mkOp4 "vadd_i"
instance (KVar a, KVar b, KVar c) => CsVaddv (S n) a b c where
vaddv = mkOp3 "vaddv"
vaddv' = mkOp6 "vaddv"
instance CsVaddv_i (S n) where
vaddv_i = mkOp3 "vaddv_i"
vaddv_i' = mkOp5 "vaddv_i"
instance CsVaget (S n) where
vaget = mkOp2 "vaget"
instance (Varable a) => CsValpass (S n) a where
valpass = mkOp4 "valpass"
valpass' = mkOp6 "valpass"
instance CsVaset (S n) where
vaset = mkOp3 "vaset"
instance (KVar a, KVar b) => CsVbap4 (S n) a b where
vbap4 = mkOp2 "vbap4"
vbap4' = mkOp4 "vbap4"
instance CsVbap4move (S n) where
vbap4move = mkOp5 "vbap4move"
instance CsVbaplsinit (S n) where
vbaplsinit = mkOp2 "vbaplsinit"
vbaplsinit' = mkOp34 "vbaplsinit"
instance (KVar a, KVar b) => CsVbapz (S n) a b where
vbapz = mkOp4 "vbapz"
vbapz' = mkOp6 "vbapz"
instance CsVbapzmove (S n) where
vbapzmove = mkOp7 "vbapzmove"
instance CsVcella (S n) where
vcella = mkOp7 "vcella"
vcella' = mkOp8 "vcella"
instance (Varable a) => CsVco2 (S n) a where
vco2 = mkOp2 "vco2"
vco2' = mkOp4 "vco2"
instance CsVco2ft (S n) where
vco2ft = mkOp1 "vco2ft"
vco2ft' = mkOp3 "vco2ft"
instance CsVco2ift (S n) where
vco2ift = mkOp1 "vco2ift"
vco2ift' = mkOp3 "vco2ift"
instance CsVco2init (S n) where
vco2init = mkOp1 "vco2init"
vco2init' = mkOp6 "vco2init"
instance (Varable a) => CsVcomb (S n) a where
vcomb = mkOp4 "vcomb"
vcomb' = mkOp6 "vcomb"
instance (KVar a, KVar b, KVar c) => CsVcopy (S n) a b c where
vcopy = mkOp3 "vcopy"
vcopy' = mkOp6 "vcopy"
instance CsVcopy_i (S n) where
vcopy_i = mkOp3 "vcopy_i"
vcopy_i' = mkOp5 "vcopy_i"
instance CsVdel_k (S n) where
vdel_k = mkOp3 "vdel_k"
vdel_k' = mkOp4 "vdel_k"
instance CsVdelayk (S n) where
vdelayk = mkOp3 "vdelayk"
vdelayk' = mkOp5 "vdelayk"
instance CsVdelayx (S n) where
vdelayx = mkOp4 "vdelayx"
vdelayx' = mkOp5 "vdelayx"
instance CsVdelayxq (S n) where
vdelayxq = mkOp7 "vdelayxq"
vdelayxq' = mkOp8 "vdelayxq"
instance CsVdelayxs (S n) where
vdelayxs = mkOp5 "vdelayxs"
vdelayxs' = mkOp6 "vdelayxs"
instance CsVdelayxw (S n) where
vdelayxw = mkOp4 "vdelayxw"
vdelayxw' = mkOp5 "vdelayxw"
instance CsVdelayxwq (S n) where
vdelayxwq = mkOp7 "vdelayxwq"
vdelayxwq' = mkOp8 "vdelayxwq"
instance CsVdelayxws (S n) where
vdelayxws = mkOp5 "vdelayxws"
vdelayxws' = mkOp6 "vdelayxws"
instance (KVar a, KVar b, KVar c) => CsVdivv (S n) a b c where
vdivv = mkOp3 "vdivv"
vdivv' = mkOp6 "vdivv"
instance CsVdivv_i (S n) where
vdivv_i = mkOp3 "vdivv_i"
vdivv_i' = mkOp5 "vdivv_i"
instance CsVecdelay (S n) where
vecdelay = mkOp5 "vecdelay"
vecdelay' = mkOp6 "vecdelay"
instance CsVeloc (S n) where
veloc = mkOp0 "veloc"
veloc' = mkOp2 "veloc"
instance (KVar a, KVar b) => CsVexp (S n) a b where
vexp = mkOp3 "vexp"
vexp' = mkOp5 "vexp"
instance CsVexp_i (S n) where
vexp_i = mkOp3 "vexp_i"
vexp_i' = mkOp4 "vexp_i"
instance CsVexpseg (S n) where
vexpseg = mkOp4 "vexpseg"
instance (KVar a, KVar b, KVar c) => CsVexpv (S n) a b c where
vexpv = mkOp3 "vexpv"
vexpv' = mkOp6 "vexpv"
instance CsVexpv_i (S n) where
vexpv_i = mkOp3 "vexpv_i"
vexpv_i' = mkOp5 "vexpv_i"
instance CsVibes (S n) where
vibes = mkOp9 "vibes"
instance CsVibr (S n) where
vibr = mkOp3 "vibr"
instance CsVibrato (S n) where
vibrato = mkOp9 "vibrato"
vibrato' = mkOp10 "vibrato"
instance CsVincr (S n) where
vincr = mkOp2 "vincr"
instance CsVlimit (S n) where
vlimit = mkOp4 "vlimit"
instance CsVlinseg (S n) where
vlinseg = mkOp4 "vlinseg"
instance CsVlowres (S n) where
vlowres = mkOp5 "vlowres"
instance CsVmap (S n) where
vmap = mkOp3 "vmap"
vmap' = mkOp5 "vmap"
instance CsVmirror (S n) where
vmirror = mkOp4 "vmirror"
instance (KVar a, KVar b) => CsVmult (S n) a b where
vmult = mkOp3 "vmult"
vmult' = mkOp5 "vmult"
instance CsVmult_i (S n) where
vmult_i = mkOp3 "vmult_i"
vmult_i' = mkOp4 "vmult_i"
instance (KVar a, KVar b, KVar c) => CsVmultv (S n) a b c where
vmultv = mkOp3 "vmultv"
vmultv' = mkOp6 "vmultv"
instance CsVmultv_i (S n) where
vmultv_i = mkOp3 "vmultv_i"
vmultv_i' = mkOp5 "vmultv_i"
instance CsVoice (S n) where
voice = mkOp8 "voice"
instance CsVosim (S n) where
vosim = mkOp7 "vosim"
vosim' = mkOp8 "vosim"
instance CsVphaseseg (S n) where
vphaseseg = mkOp4 "vphaseseg"
instance CsVport (S n) where
vport = mkOp3 "vport"
vport' = mkOp4 "vport"
instance (KVar a, KVar b) => CsVpow (S n) a b where
vpow = mkOp3 "vpow"
vpow' = mkOp5 "vpow"
instance CsVpow_i (S n) where
vpow_i = mkOp3 "vpow_i"
vpow_i' = mkOp4 "vpow_i"
instance (KVar a, KVar b, KVar c) => CsVpowv (S n) a b c where
vpowv = mkOp3 "vpowv"
vpowv' = mkOp6 "vpowv"
instance CsVpowv_i (S n) where
vpowv_i = mkOp3 "vpowv_i"
vpowv_i' = mkOp5 "vpowv_i"
instance CsVpvoc (S n) where
vpvoc = mkOp3 "vpvoc"
vpvoc' = mkOp5 "vpvoc"
instance CsVrandh (S n) where
vrandh = mkOp4 "vrandh"
vrandh' = mkOp8 "vrandh"
instance CsVrandi (S n) where
vrandi = mkOp4 "vrandi"
vrandi' = mkOp8 "vrandi"
instance (KVar a, KVar b, KVar c) => CsVsubv (S n) a b c where
vsubv = mkOp3 "vsubv"
vsubv' = mkOp6 "vsubv"
instance CsVsubv_i (S n) where
vsubv_i = mkOp3 "vsubv_i"
vsubv_i' = mkOp5 "vsubv_i"
instance CsVtaba (S n) where
vtaba = mkOp3 "vtaba"
instance CsVtabi (S n) where
vtabi = mkOp3 "vtabi"
instance CsVtabk (S n) where
vtabk = mkOp3 "vtabk"
instance CsVtable1k (S n) where
vtable1k = mkOp2 "vtable1k"
instance CsVtablea (S n) where
vtablea = mkOp5 "vtablea"
instance CsVtablei (S n) where
vtablei = mkOp5 "vtablei"
instance CsVtablek (S n) where
vtablek = mkOp5 "vtablek"
instance CsVtablewa (S n) where
vtablewa = mkOp4 "vtablewa"
instance CsVtablewi (S n) where
vtablewi = mkOp4 "vtablewi"
instance CsVtablewk (S n) where
vtablewk = mkOp4 "vtablewk"
instance CsVtabwa (S n) where
vtabwa = mkOp3 "vtabwa"
instance CsVtabwi (S n) where
vtabwi = mkOp3 "vtabwi"
instance CsVtabwk (S n) where
vtabwk = mkOp3 "vtabwk"
instance CsVwrap (S n) where
vwrap = mkOp4 "vwrap"
instance CsWaveset (S n) where
waveset = mkOp2 "waveset"
waveset' = mkOp3 "waveset"
instance CsWeibull (S n) (ASig (S n)) where
weibull = mkOp2 "weibull"
instance CsWeibull (S n) (KSig (S n)) where
weibull = mkOp2 "weibull"
instance CsWeibull (S n) (INum (S n)) where
weibull = mkOp2 "weibull"
instance CsWgbow (S n) where
wgbow = mkOp7 "wgbow"
wgbow' = mkOp8 "wgbow"
instance CsWgbowedbar (S n) where
wgbowedbar = mkOp5 "wgbowedbar"
wgbowedbar' = mkOp9 "wgbowedbar"
instance CsWgbrass (S n) where
wgbrass = mkOp7 "wgbrass"
wgbrass' = mkOp8 "wgbrass"
instance CsWgclar (S n) where
wgclar = mkOp9 "wgclar"
wgclar' = mkOp10 "wgclar"
instance CsWgflute (S n) where
wgflute = mkOp9 "wgflute"
wgflute' = mkOp12 "wgflute"
instance CsWgpluck (S n) where
wgpluck = mkOp7 "wgpluck"
instance CsWgpluck2 (S n) where
wgpluck2 = mkOp5 "wgpluck2"
instance (Varable a) => CsWguide1 (S n) a where
wguide1 = mkOp4 "wguide1"
instance (Varable a, Varable b) => CsWguide2 (S n) a b where
wguide2 = mkOp7 "wguide2"
instance CsWrap (S n) (ASig (S n)) (ASig (S n)) where
wrap = mkOp3 "wrap"
instance CsWrap (S n) (KSig (S n)) (KSig (S n)) where
wrap = mkOp3 "wrap"
instance CsWrap (S n) (INum (S n)) (INum (S n)) where
wrap = mkOp3 "wrap"
instance CsWterrain (S n) where
wterrain = mkOp8 "wterrain"
instance (PVar out) => CsXadsr (S n) out where
xadsr = mkOp4 "xadsr"
xadsr' = mkOp5 "xadsr"
instance (Varable a, Varable b) => CsXor (S n) (ASig (S n)) a b where
xor = mkOp2 "xor"
instance CsXor (S n) (KSig (S n)) (KSig (S n)) (KSig (S n)) where
xor = mkOp2 "xor"
instance CsXor (S n) (INum (S n)) (INum (S n)) (INum (S n)) where
xor = mkOp2 "xor"
instance CsXout (S n) where
xout = mkOp1 "xout"
instance CsXscanmap (S n) where
xscanmap = mkOp3 "xscanmap"
xscanmap' = mkOp4 "xscanmap"
instance CsXscans (S n) where
xscans = mkOp4 "xscans"
xscans' = mkOp5 "xscans"
instance CsXscansmap (S n) where
xscansmap = mkOp5 "xscansmap"
xscansmap' = mkOp6 "xscansmap"
instance CsXscanu (S n) where
xscanu = mkOp18 "xscanu"
instance CsXtratim (S n) where
xtratim = mkOp1 "xtratim"
instance CsXyin (S n) where
xyin = mkOp5 "xyin"
xyin' = mkOp7 "xyin"
instance CsZacl (S n) where
zacl = mkOp2 "zacl"
instance CsZakinit (S n) where
zakinit = mkOp2 "zakinit"
instance CsZamod (S n) where
zamod = mkOp2 "zamod"
instance CsZar (S n) where
zar = mkOp1 "zar"
instance CsZarg (S n) where
zarg = mkOp2 "zarg"
instance CsZaw (S n) where
zaw = mkOp2 "zaw"
instance CsZawm (S n) where
zawm = mkOp2 "zawm"
zawm' = mkOp3 "zawm"
instance CsZfilter2 (S n) where
zfilter2 = mkOp6 "zfilter2"
instance CsZir (S n) where
zir = mkOp1 "zir"
instance CsZiw (S n) where
ziw = mkOp2 "ziw"
instance CsZiwm (S n) where
ziwm = mkOp2 "ziwm"
ziwm' = mkOp3 "ziwm"
instance CsZkcl (S n) where
zkcl = mkOp2 "zkcl"
instance CsZkmod (S n) where
zkmod = mkOp2 "zkmod"
instance CsZkr (S n) where
zkr = mkOp1 "zkr"
instance CsZkw (S n) where
zkw = mkOp2 "zkw"
instance CsZkwm (S n) where
zkwm = mkOp2 "zkwm"
zkwm' = mkOp3 "zkwm"