module Csound.Typed.Opcode.InstrumentControl (
    
    
    -- * Clock Control.
    clockoff, clockon,
    
    -- * Duration Control.
    ihold, turnoff, turnoff2, turnon,
    
    -- * Invocation.
    event, event_i, mute, readscore, remove, schedkwhen, schedkwhennamed, schedule, schedwhen, scoreline, scoreline_i,
    
    -- * Realtime Performance Control.
    active, cpuprc, exitnow, jacktransport, maxalloc, prealloc,
    
    -- * Sensing and Control.
    button, changed, checkbox, control, follow, follow2, getcfg, joystick, metro, miditempo, p5gconnect, p5gdata, pcount, peak, pindex, pitch, pitchamdf, plltrack, ptrack, rewindscore, rms, sensekey, seqtime, seqtime2, setctrl, splitrig, tempest, tempo, tempoval, timedseq, trigger, trigseq, wiiconnect, wiidata, wiirange, wiisend, xyin,
    
    -- * Stacks.
    pop, pop_f, push, push_f, stack,
    
    -- * Subinstrument Control.
    subinstr, subinstrinit,
    
    -- * Time Reading.
    date, dates, readclock, rtclock, timeinstk, timeinsts, timek, times) where

import Control.Applicative
import Control.Monad.Trans.Class
import Csound.Dynamic
import Csound.Typed

-- Clock Control.

-- | 
-- Stops one of a number of internal clocks.
--
-- >  clockoff  inum
--
-- csound doc: <http://www.csounds.com/manual/html/clockoff.html>
clockoff ::  D -> SE ()
clockoff b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1
    where f a1 = opcs "clockoff" [(Xr,[Ir])] [a1]

-- | 
-- Starts one of a number of internal clocks.
--
-- >  clockon  inum
--
-- csound doc: <http://www.csounds.com/manual/html/clockon.html>
clockon ::  D -> SE ()
clockon b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1
    where f a1 = opcs "clockon" [(Xr,[Ir])] [a1]

-- Duration Control.

-- | 
-- Creates a held note.
--
-- Causes a finite-duration note to become a “held” note
--
-- >  ihold  
--
-- csound doc: <http://www.csounds.com/manual/html/ihold.html>
ihold ::   SE ()
ihold  = SE $ (depT_ =<<) $ lift $ return $ f 
    where f  = opcs "ihold" [(Xr,[])] []

-- | 
-- Enables an instrument to turn itself off.
--
-- >  turnoff  
--
-- csound doc: <http://www.csounds.com/manual/html/turnoff.html>
turnoff ::   SE ()
turnoff  = SE $ (depT_ =<<) $ lift $ return $ f 
    where f  = opcs "turnoff" [(Xr,[])] []

-- | 
-- Turn off instance(s) of other instruments at performance time.
--
-- >  turnoff2  kinsno, kmode, krelease
-- >         
--
-- csound doc: <http://www.csounds.com/manual/html/turnoff2.html>
turnoff2 ::  Sig -> Sig -> Sig -> SE ()
turnoff2 b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3
    where f a1 a2 a3 = opcs "turnoff2" [(Xr,[Kr,Kr,Kr])] [a1,a2,a3]

-- | 
-- Activate an instrument for an indefinite time.
--
-- >  turnon  insnum [, itime]
--
-- csound doc: <http://www.csounds.com/manual/html/turnon.html>
turnon ::  D -> SE ()
turnon b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1
    where f a1 = opcs "turnon" [(Xr,[Ir,Ir])] [a1]

-- Invocation.

-- | 
-- Generates a score event from an instrument.
--
-- >  event  "scorechar", kinsnum, kdelay, kdur, [, kp4] [, kp5] [, ...]
-- >  event  "scorechar", "insname", kdelay, kdur, [, kp4] [, kp5] [, ...]
--
-- csound doc: <http://www.csounds.com/manual/html/event.html>
event ::  Str -> Sig -> Sig -> Sig -> [Sig] -> SE ()
event b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unStr b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> mapM unSig b5
    where f a1 a2 a3 a4 a5 = opcs "event" [(Xr,[Sr] ++ (repeat Kr))] ([a1,a2,a3,a4] ++ a5)

-- | 
-- Generates a score event from an instrument.
--
-- >  event_i  "scorechar", iinsnum, idelay, idur, [, ip4] [, ip5] [, ...]
-- >  event_i  "scorechar", "insname", idelay, idur, [, ip4] [, ip5] [, ...]
--
-- csound doc: <http://www.csounds.com/manual/html/event_i.html>
event_i ::  Str -> D -> D -> D -> [D] -> SE ()
event_i b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unStr b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> mapM unD b5
    where f a1 a2 a3 a4 a5 = opcs "event_i" [(Xr,[Sr] ++ (repeat Ir))] ([a1,a2,a3,a4] ++ a5)

-- | 
-- Mutes/unmutes new instances of a given instrument.
--
-- >  mute  insnum [, iswitch]
-- >  mute  "insname" [, iswitch]
--
-- csound doc: <http://www.csounds.com/manual/html/mute.html>
mute ::  D -> SE ()
mute b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1
    where f a1 = opcs "mute" [(Xr,[Ir,Ir])] [a1]

-- | 
-- Read, preprocess and schedule a score from an input string.
--
-- Readscore will issue one or more score events. 
-- 	  It can handle strings in the same conditions as
-- 	  the standard score, including preprocessing (carry, sort, ramp, etc). 
-- Multi-line strings are accepted, using {{  }} to enclose the string.
--
-- >  readscore  Sin 
--
-- csound doc: <http://www.csounds.com/manual/html/readscore.html>
readscore ::  Str -> SE ()
readscore b1 = SE $ (depT_ =<<) $ lift $ f <$> unStr b1
    where f a1 = opcs "readscore" [(Xr,[Sr])] [a1]

-- | 
-- Removes the definition of an instrument.
--
-- Removes the definition of an instrument as long as it is not in use.
--
-- >  remove  insnum
--
-- csound doc: <http://www.csounds.com/manual/html/remove.html>
remove ::  D -> SE ()
remove b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1
    where f a1 = opcs "remove" [(Xr,[Ir])] [a1]

-- | 
-- Adds a new score event generated by a k-rate trigger.
--
-- >  schedkwhen  ktrigger, kmintim, kmaxnum, kinsnum, kwhen, kdur \
-- >           [, ip4] [, ip5] [...]
-- >  schedkwhen  ktrigger, kmintim, kmaxnum, "insname", kwhen, kdur \
-- >           [, ip4] [, ip5] [...]
--
-- csound doc: <http://www.csounds.com/manual/html/schedkwhen.html>
schedkwhen ::  Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
schedkwhen b1 b2 b3 b4 b5 b6 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 <*> unSig b6
    where f a1 a2 a3 a4 a5 a6 = opcs "schedkwhen" [(Xr,[Kr,Kr,Kr,Kr,Kr,Kr] ++ (repeat Ir))] [a1
                                                                                            ,a2
                                                                                            ,a3
                                                                                            ,a4
                                                                                            ,a5
                                                                                            ,a6]

-- | 
-- Similar to schedkwhen but uses a named instrument at init-time.
--
-- >  schedkwhennamed  ktrigger, kmintim, kmaxnum, "name", kwhen, kdur \
-- >           [, ip4] [, ip5] [...]
--
-- csound doc: <http://www.csounds.com/manual/html/schedkwhennamed.html>
schedkwhennamed ::  Sig -> Sig -> Sig -> Str -> Sig -> Sig -> SE ()
schedkwhennamed b1 b2 b3 b4 b5 b6 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unStr b4 <*> unSig b5 <*> unSig b6
    where f a1 a2 a3 a4 a5 a6 = opcs "schedkwhennamed" [(Xr,[Kr,Kr,Kr,Sr,Kr,Kr] ++ (repeat Ir))] [a1
                                                                                                 ,a2
                                                                                                 ,a3
                                                                                                 ,a4
                                                                                                 ,a5
                                                                                                 ,a6]

-- | 
-- Adds a new score event.
--
-- >  schedule  insnum, iwhen, idur [, ip4] [, ip5] [...]
-- >  schedule  "insname", iwhen, idur [, ip4] [, ip5] [...]
--
-- csound doc: <http://www.csounds.com/manual/html/schedule.html>
schedule ::  D -> D -> D -> SE ()
schedule b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3
    where f a1 a2 a3 = opcs "schedule" [(Xr,(repeat Ir))] [a1,a2,a3]

-- | 
-- Adds a new score event.
--
-- >  schedwhen  ktrigger, kinsnum, kwhen, kdur [, ip4] [, ip5] [...]
-- >  schedwhen  ktrigger, "insname", kwhen, kdur [, ip4] [, ip5] [...]
--
-- csound doc: <http://www.csounds.com/manual/html/schedwhen.html>
schedwhen ::  Sig -> Sig -> Sig -> Sig -> SE ()
schedwhen b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4
    where f a1 a2 a3 a4 = opcs "schedwhen" [(Xr,[Kr,Kr,Kr,Kr] ++ (repeat Ir))] [a1,a2,a3,a4]

-- | 
-- Issues one or more score line events from an instrument.
--
-- Scoreline will issue one or more score events, if ktrig is 1 every k-period. 
-- 	  It can handle strings in the same conditions as
-- 	  the standard score. Multi-line strings are accepted, using {{  }} to enclose the string.
--
-- >  scoreline  Sin, ktrig
--
-- csound doc: <http://www.csounds.com/manual/html/scoreline.html>
scoreline ::  Str -> Sig -> SE ()
scoreline b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unStr b1 <*> unSig b2
    where f a1 a2 = opcs "scoreline" [(Xr,[Sr,Kr])] [a1,a2]

-- | 
-- Issues one or more score line events from an instrument at i-time.
--
-- scoreline_i will issue score events at i-time.  It can handle strings in the same conditions as the standard score. Multi-line strings are accepted, using {{  }} to enclose the string.
--
-- >  scoreline_i  Sin
--
-- csound doc: <http://www.csounds.com/manual/html/scoreline_i.html>
scoreline_i ::  Str -> SE ()
scoreline_i b1 = SE $ (depT_ =<<) $ lift $ f <$> unStr b1
    where f a1 = opcs "scoreline_i" [(Xr,[Sr])] [a1]

-- Realtime Performance Control.

-- | 
-- Returns the number of active instances of an instrument.
--
-- > ir  active  insnum [,iopt]
-- > ir  active  Sinsname [,iopt]
-- > kres  active  kinsnum [,iopt]
--
-- csound doc: <http://www.csounds.com/manual/html/active.html>
active ::  D -> Sig
active b1 = Sig $ f <$> unD b1
    where f a1 = opcs "active" [(Ir,[Ir,Ir]),(Ir,[Sr,Ir]),(Kr,[Kr,Ir])] [a1]

-- | 
-- Control allocation of cpu resources on a per-instrument basis, to optimize realtime output.
--
-- >  cpuprc  insnum, ipercent
-- >  cpuprc  Sinsname, ipercent
--
-- csound doc: <http://www.csounds.com/manual/html/cpuprc.html>
cpuprc ::  D -> D -> SE ()
cpuprc b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2
    where f a1 a2 = opcs "cpuprc" [(Xr,[Ir,Ir])] [a1,a2]

-- | 
-- Exit Csound as fast as possible, with no cleaning up.
--
-- In Csound4 calls an exit function to leave Csound as fast as
--     possible. On Csound5 exits back to the driving code.
--
-- >  exitnow  
--
-- csound doc: <http://www.csounds.com/manual/html/exitnow.html>
exitnow ::   SE ()
exitnow  = SE $ (depT_ =<<) $ lift $ return $ f 
    where f  = opcs "exitnow" [(Xr,[])] []

-- | 
-- Start/stop jack_transport and can optionally relocate the playback head.
--
-- >  jacktransport  icommand [, ilocation]
--
-- csound doc: <http://www.csounds.com/manual/html/jacktransport.html>
jacktransport ::  D -> SE ()
jacktransport b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1
    where f a1 = opcs "jacktransport" [(Xr,[Ir,Ir])] [a1]

-- | 
-- Limits the number of allocations of an instrument.
--
-- >  maxalloc  insnum, icount
-- >  maxalloc  Sinsname, icount
--
-- csound doc: <http://www.csounds.com/manual/html/maxalloc.html>
maxalloc ::  D -> D -> SE ()
maxalloc b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2
    where f a1 a2 = opcs "maxalloc" [(Xr,[Ir,Ir])] [a1,a2]

-- | 
-- Creates space for instruments but does not run them.
--
-- >  prealloc  insnum, icount
-- >  prealloc  "insname", icount
--
-- csound doc: <http://www.csounds.com/manual/html/prealloc.html>
prealloc ::  D -> D -> SE ()
prealloc b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2
    where f a1 a2 = opcs "prealloc" [(Xr,[Ir,Ir])] [a1,a2]

-- Sensing and Control.

-- | 
-- Sense on-screen controls.
--
-- Sense on-screen controls. Requires Winsound or TCL/TK.
--
-- > kres  button  knum
--
-- csound doc: <http://www.csounds.com/manual/html/button.html>
button ::  Sig -> Sig
button b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "button" [(Kr,[Kr])] [a1]

-- | 
-- k-rate signal change detector.
--
-- This opcode outputs a trigger signal that informs when any one of its k-rate arguments has changed. Useful with valuator widgets or MIDI controllers.
--
-- > ktrig  changed  kvar1 [, kvar2,..., kvarN]
--
-- csound doc: <http://www.csounds.com/manual/html/changed.html>
changed ::  [Sig] -> Sig
changed b1 = Sig $ f <$> mapM unSig b1
    where f a1 = opcs "changed" [(Kr,(repeat Kr))] a1

-- | 
-- Sense on-screen controls.
--
-- Sense on-screen controls. Requires Winsound or TCL/TK.
--
-- > kres  checkbox  knum
--
-- csound doc: <http://www.csounds.com/manual/html/checkbox.html>
checkbox ::  Sig -> Sig
checkbox b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "checkbox" [(Kr,[Kr])] [a1]

-- | 
-- Configurable slider controls for realtime user input.
--
-- Configurable slider controls for realtime user input. Requires Winsound or TCL/TK. control reads a slider's value.
--
-- > kres  control  knum
--
-- csound doc: <http://www.csounds.com/manual/html/control.html>
control ::  Sig -> Sig
control b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "control" [(Kr,[Kr])] [a1]

-- | 
-- Envelope follower unit generator.
--
-- > ares  follow  asig, idt
--
-- csound doc: <http://www.csounds.com/manual/html/follow.html>
follow ::  Sig -> D -> Sig
follow b1 b2 = Sig $ f <$> unSig b1 <*> unD b2
    where f a1 a2 = opcs "follow" [(Ar,[Ar,Ir])] [a1,a2]

-- | 
-- Another controllable envelope extractor.
--
-- A controllable envelope extractor using the algorithm attributed to Jean-Marc Jot.
--
-- > ares  follow2  asig, katt, krel
--
-- csound doc: <http://www.csounds.com/manual/html/follow2.html>
follow2 ::  Sig -> Sig -> Sig -> Sig
follow2 b1 b2 b3 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unSig b3
    where f a1 a2 a3 = opcs "follow2" [(Ar,[Ar,Kr,Kr])] [a1,a2,a3]

-- | 
-- Return Csound settings.
--
-- Return various configuration settings in Svalue as a string at init time.
--
-- > Svalue  getcfg  iopt
--
-- csound doc: <http://www.csounds.com/manual/html/getcfg.html>
getcfg ::  D -> Str
getcfg b1 = Str $ f <$> unD b1
    where f a1 = opcs "getcfg" [(Sr,[Ir])] [a1]

-- | 
-- Reads data from a joystick controller.
--
-- Reads data from a Linux joystick controller
--
-- > kres  joystick  kdevice ktab
--
-- csound doc: <http://www.csounds.com/manual/html/joystick.html>
joystick ::  Sig -> Sig -> Sig
joystick b1 b2 = Sig $ f <$> unSig b1 <*> unSig b2
    where f a1 a2 = opcs "joystick" [(Kr,[Kr,Kr])] [a1,a2]

-- | 
-- Trigger Metronome
--
-- Generate a metronomic signal to be used in any circumstance an isochronous trigger is needed.
--
-- > ktrig   metro   kfreq [, initphase]
--
-- csound doc: <http://www.csounds.com/manual/html/metro.html>
metro ::  Sig -> Sig
metro b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "metro" [(Kr,[Kr,Ir])] [a1]

-- | 
-- Returns the current tempo at k-rate, of either the MIDI file (if available) or the score
--
-- > ksig   miditempo  
--
-- csound doc: <http://www.csounds.com/manual/html/miditempo.html>
miditempo ::   Sig
miditempo  = Sig $ return $ f 
    where f  = opcs "miditempo" [(Kr,[])] []

-- | 
-- Reads data from a P5 Glove controller.
--
-- Opens and at control-rate polls a P5 Glove controller.
--
-- >  p5gconnect  
--
-- csound doc: <http://www.csounds.com/manual/html/p5gconnect.html>
p5gconnect ::   SE ()
p5gconnect  = SE $ (depT_ =<<) $ lift $ return $ f 
    where f  = opcs "p5gconnect" [(Xr,[])] []

-- | 
-- Reads data fields from an external P5 Glove.
--
-- Reads data fields from a P5 Glove controller.
--
-- > kres  p5gdata  kcontrol
--
-- csound doc: <http://www.csounds.com/manual/html/p5gdata.html>
p5gdata ::  Sig -> Sig
p5gdata b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "p5gdata" [(Kr,[Kr])] [a1]

-- | 
-- Returns the number of pfields belonging to a note event.
--
-- pcount returns the number of pfields belonging to a note event.
--
-- > icount  pcount  
--
-- csound doc: <http://www.csounds.com/manual/html/pcount.html>
pcount ::   D
pcount  = D $ return $ f 
    where f  = opcs "pcount" [(Ir,[])] []

-- | 
-- Maintains the output equal to the highest absolute value received.
--
-- These opcodes maintain the output k-rate variable as the peak absolute level so far received.
--
-- > kres  peak  asig
-- > kres  peak  ksig
--
-- csound doc: <http://www.csounds.com/manual/html/peak.html>
peak ::  Sig -> Sig
peak b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "peak" [(Kr,[Ar]),(Kr,[Kr])] [a1]

-- | 
-- Returns the value of a specified pfield.
--
-- pindex returns the value of a specified pfield.
--
-- > ivalue  pindex  ipfieldIndex
--
-- csound doc: <http://www.csounds.com/manual/html/pindex.html>
pindex ::  D -> D
pindex b1 = D $ f <$> unD b1
    where f a1 = opcs "pindex" [(Ir,[Ir])] [a1]

-- | 
-- Tracks the pitch of a signal.
--
-- Using the same techniques as spectrum and specptrk, pitch tracks the pitch of the signal in octave point decimal form, and amplitude in dB.
--
-- > koct, kamp  pitch  asig, iupdte, ilo, ihi, idbthresh [, ifrqs] [, iconf] \
-- >           [, istrt] [, iocts] [, iq] [, inptls] [, irolloff] [, iskip]
--
-- csound doc: <http://www.csounds.com/manual/html/pitch.html>
pitch ::  Sig -> D -> D -> D -> D -> (Sig,Sig)
pitch b1 b2 b3 b4 b5 = pureTuple $ f <$> unSig b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5
    where f a1 a2 a3 a4 a5 = mopcs "pitch" ([Kr,Kr],[Ar,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir]) [a1
                                                                                              ,a2
                                                                                              ,a3
                                                                                              ,a4
                                                                                              ,a5]

-- | 
-- Follows the pitch of a signal based on the AMDF method.
--
-- Follows the pitch of a signal based on the AMDF method (Average Magnitude Difference Function). Outputs pitch and amplitude tracking signals. The method is quite fast and should run in realtime. This technique usually works best for monophonic signals.
--
-- > kcps, krms  pitchamdf  asig, imincps, imaxcps [, icps] [, imedi] \
-- >           [, idowns] [, iexcps] [, irmsmedi]
--
-- csound doc: <http://www.csounds.com/manual/html/pitchamdf.html>
pitchamdf ::  Sig -> D -> D -> (Sig,Sig)
pitchamdf b1 b2 b3 = pureTuple $ f <$> unSig b1 <*> unD b2 <*> unD b3
    where f a1 a2 a3 = mopcs "pitchamdf" ([Kr,Kr],[Ar,Ir,Ir,Ir,Ir,Ir,Ir,Ir]) [a1,a2,a3]

-- | 
-- Tracks the pitch of a signal.
--
-- plltrack, a pitch tracker based on a phase-locked loop algorithm, described in Zolzer, U, Sankarababu, S.V. and Moller, S, "PLL-based Pitch Detection and Tracking for Audio Signals. Proc. of IIH-MSP 2012".
--
-- > acps, alock  plltrack  asig, kd [, kloopf, kloopq, klf, khf, kthresh]
--
-- csound doc: <http://www.csounds.com/manual/html/plltrack.html>
plltrack ::  Sig -> Sig -> (Sig,Sig)
plltrack b1 b2 = pureTuple $ f <$> unSig b1 <*> unSig b2
    where f a1 a2 = mopcs "plltrack" ([Ar,Ar],[Ar,Kr,Kr,Kr,Kr,Kr,Kr]) [a1,a2]

-- | 
-- Tracks the pitch of a signal.
--
-- ptrack takes an input signal, splits it into ihopsize blocks and using a STFT method, extracts an estimated pitch for its fundamental frequency as well as estimating the total amplitude of the signal in dB, relative to full-scale (0dB). The method implies an analysis window size of 2*ihopsize samples (overlaping by 1/2 window), which has to be a power-of-two, between 128 and 8192 (hopsizes between 64 and 4096). Smaller windows will give better time precision, but worse frequency accuracy (esp. in low fundamentals).This opcode is based on an original algorithm by M. Puckette.
--
-- > kcps, kamp  ptrack  asig, ihopsize[,ipeaks]
--
-- csound doc: <http://www.csounds.com/manual/html/ptrack.html>
ptrack ::  Sig -> D -> (Sig,Sig)
ptrack b1 b2 = pureTuple $ f <$> unSig b1 <*> unD b2
    where f a1 a2 = mopcs "ptrack" ([Kr,Kr],[Ar,Ir,Ir]) [a1,a2]

-- | 
-- Rewinds the playback position of the current score performance.
--
-- Rewinds the playback position of the current score performance..
--
-- >   rewindscore  
--
-- csound doc: <http://www.csounds.com/manual/html/rewindscore.html>
rewindscore ::   SE ()
rewindscore  = SE $ (depT_ =<<) $ lift $ return $ f 
    where f  = opcs "rewindscore" [(Xr,[])] []

-- | 
-- Determines the root-mean-square amplitude of an audio signal.
--
-- Determines the root-mean-square amplitude of an audio signal. It low-pass filters the actual value, to average in the manner of a VU meter.
--
-- > kres  rms  asig [, ihp] [, iskip]
--
-- csound doc: <http://www.csounds.com/manual/html/rms.html>
rms ::  Sig -> Sig
rms b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "rms" [(Kr,[Ar,Ir,Ir])] [a1]

-- | 
-- Returns the ASCII code of a key that has been pressed.
--
-- Returns the ASCII code of a key that has been pressed, or -1 if no key has been pressed.
--
-- > kres[, kkeydown]  sensekey  
--
-- csound doc: <http://www.csounds.com/manual/html/sensekey.html>
sensekey :: Tuple a =>  a
sensekey  = pureTuple $ return $ f 
    where f  = mopcs "sensekey" ([Kr,Kr],[]) []

-- | 
-- Generates a trigger signal according to the values stored in a table.
--
-- > ktrig_out  seqtime  ktime_unit, kstart, kloop, kinitndx, kfn_times
--
-- csound doc: <http://www.csounds.com/manual/html/seqtime.html>
seqtime ::  Sig -> Sig -> Sig -> Sig -> Tab -> Sig
seqtime b1 b2 b3 b4 b5 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unTab b5
    where f a1 a2 a3 a4 a5 = opcs "seqtime" [(Kr,[Kr,Kr,Kr,Kr,Kr])] [a1,a2,a3,a4,a5]

-- | 
-- Generates a trigger signal according to the values stored in a table.
--
-- > ktrig_out  seqtime2  ktrig_in, ktime_unit, kstart, kloop, kinitndx, kfn_times
--
-- csound doc: <http://www.csounds.com/manual/html/seqtime2.html>
seqtime2 ::  Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig
seqtime2 b1 b2 b3 b4 b5 b6 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 <*> unTab b6
    where f a1 a2 a3 a4 a5 a6 = opcs "seqtime2" [(Kr,[Kr,Kr,Kr,Kr,Kr,Kr])] [a1,a2,a3,a4,a5,a6]

-- | 
-- Configurable slider controls for realtime user input.
--
-- Configurable slider controls for realtime user input. Requires Winsound or TCL/TK. setctrl sets a slider to a specific value, or sets a minimum or maximum range.
--
-- >  setctrl  inum, ival, itype
--
-- csound doc: <http://www.csounds.com/manual/html/setctrl.html>
setctrl ::  D -> D -> D -> SE ()
setctrl b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3
    where f a1 a2 a3 = opcs "setctrl" [(Xr,[Ir,Ir,Ir])] [a1,a2,a3]

-- | 
-- Split a trigger signal
--
-- splitrig splits a trigger signal (i.e. a timed sequence of control-rate impulses) into several channels following a structure designed by the user.
--
-- >  splitrig  ktrig, kndx, imaxtics, ifn, kout1 [,kout2,...,koutN]
--
-- csound doc: <http://www.csounds.com/manual/html/splitrig.html>
splitrig ::  Sig -> Sig -> D -> Tab -> [Sig] -> SE ()
splitrig b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unD b3 <*> unTab b4 <*> mapM unSig b5
    where f a1 a2 a3 a4 a5 = opcs "splitrig" [(Xr,[Kr,Kr,Ir,Ir] ++ (repeat Kr))] ([a1
                                                                                  ,a2
                                                                                  ,a3
                                                                                  ,a4] ++ a5)

-- | 
-- Estimate the tempo of beat patterns in a control signal.
--
-- > ktemp  tempest  kin, iprd, imindur, imemdur, ihp, ithresh, ihtim, ixfdbak, \
-- >           istartempo, ifn [, idisprd] [, itweek]
--
-- csound doc: <http://www.csounds.com/manual/html/tempest.html>
tempest ::  Sig -> D -> D -> D -> D -> D -> D -> D -> D -> Tab -> Sig
tempest b1 b2 b3 b4 b5 b6 b7 b8 b9 b10 = Sig $ f <$> unSig b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 <*> unD b6 <*> unD b7 <*> unD b8 <*> unD b9 <*> unTab b10
    where f a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 = opcs "tempest" [(Kr
                                                             ,[Kr,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5,a6,a7,a8,a9,a10]

-- | 
-- Apply tempo control to an uninterpreted score.
--
-- >  tempo  ktempo, istartempo
--
-- csound doc: <http://www.csounds.com/manual/html/tempo.html>
tempo ::  Sig -> D -> SE ()
tempo b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unD b2
    where f a1 a2 = opcs "tempo" [(Xr,[Kr,Ir])] [a1,a2]

-- | 
-- Reads the current value of the tempo.
--
-- > kres  tempoval  
--
-- csound doc: <http://www.csounds.com/manual/html/tempoval.html>
tempoval ::   Sig
tempoval  = Sig $ return $ f 
    where f  = opcs "tempoval" [(Kr,[])] []

-- | 
-- Time Variant Sequencer
--
-- An event-sequencer in which time can be controlled by a
--     time-pointer. Sequence data are stored into a table.
--
-- > ktrig   timedseq   ktimpnt, ifn, kp1 [,kp2, kp3, ...,kpN]
--
-- csound doc: <http://www.csounds.com/manual/html/timedseq.html>
timedseq ::  Sig -> Tab -> [Sig] -> Sig
timedseq b1 b2 b3 = Sig $ f <$> unSig b1 <*> unTab b2 <*> mapM unSig b3
    where f a1 a2 a3 = opcs "timedseq" [(Kr,[Kr,Ir] ++ (repeat Kr))] ([a1,a2] ++ a3)

-- | 
-- Informs when a krate signal crosses a threshold.
--
-- > kout  trigger  ksig, kthreshold, kmode
--
-- csound doc: <http://www.csounds.com/manual/html/trigger.html>
trigger ::  Sig -> Sig -> Sig -> Sig
trigger b1 b2 b3 = Sig $ f <$> unSig b1 <*> unSig b2 <*> unSig b3
    where f a1 a2 a3 = opcs "trigger" [(Kr,[Kr,Kr,Kr])] [a1,a2,a3]

-- | 
-- Accepts a trigger signal as input and outputs a group of values.
--
-- >  trigseq  ktrig_in, kstart, kloop, kinitndx, kfn_values, kout1 [, kout2] [...]
--
-- csound doc: <http://www.csounds.com/manual/html/trigseq.html>
trigseq ::  Sig -> Sig -> Sig -> Sig -> Tab -> [Sig] -> SE ()
trigseq b1 b2 b3 b4 b5 b6 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unTab b5 <*> mapM unSig b6
    where f a1 a2 a3 a4 a5 a6 = opcs "trigseq" [(Xr,(repeat Kr))] ([a1,a2,a3,a4,a5] ++ a6)

-- | 
-- Reads data from a number of external Nintendo Wiimote controllers.
--
-- Opens and at control-rate polls up to four external Nintendo Wiimote controllers.
--
-- > ires  wiiconnect  [itimeout, imaxnum]
--
-- csound doc: <http://www.csounds.com/manual/html/wiiconnect.html>
wiiconnect ::   D
wiiconnect  = D $ return $ f 
    where f  = opcs "wiiconnect" [(Ir,[Ir,Ir])] []

-- | 
-- Reads data fields from a number of external Nintendo Wiimote controllers.
--
-- Reads data fields from upto four external Nintendo Wiimote controllers.
--
-- > kres  wiidata  kcontrol[, knum]
--
-- csound doc: <http://www.csounds.com/manual/html/wiidata.html>
wiidata ::  Sig -> Sig
wiidata b1 = Sig $ f <$> unSig b1
    where f a1 = opcs "wiidata" [(Kr,[Kr,Kr])] [a1]

-- | 
-- Sets scaling and range limits for certain Wiimote fields.
--
-- >   wiirange  icontrol, iminimum, imaximum[, inum]
--
-- csound doc: <http://www.csounds.com/manual/html/wiirange.html>
wiirange ::  D -> D -> D -> SE ()
wiirange b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3
    where f a1 a2 a3 = opcs "wiirange" [(Xr,[Ir,Ir,Ir,Ir])] [a1,a2,a3]

-- | 
-- Sends data to one of a number of external Nintendo Wiimote controllers.
--
-- > kres  wiisend  kcontrol, kvalue[, knum]
--
-- csound doc: <http://www.csounds.com/manual/html/wiisend.html>
wiisend ::  Sig -> Sig -> Sig
wiisend b1 b2 = Sig $ f <$> unSig b1 <*> unSig b2
    where f a1 a2 = opcs "wiisend" [(Kr,[Kr,Kr,Kr])] [a1,a2]

-- | 
-- Sense the cursor position in an output window
--
-- Sense the cursor position in an output window. When xyin is called the position of the mouse within the output window is used to reply to the request.  This simple mechanism does mean that only one xyin can be used accurately at once.  The position of the mouse is reported in the output window.
--
-- > kx, ky  xyin  iprd, ixmin, ixmax, iymin, iymax [, ixinit] [, iyinit]
--
-- csound doc: <http://www.csounds.com/manual/html/xyin.html>
xyin ::  D -> D -> D -> D -> D -> (Sig,Sig)
xyin b1 b2 b3 b4 b5 = pureTuple $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5
    where f a1 a2 a3 a4 a5 = mopcs "xyin" ([Kr,Kr],[Ir,Ir,Ir,Ir,Ir,Ir,Ir]) [a1,a2,a3,a4,a5]

-- Stacks.

-- | 
-- Pops values from the global stack.
--
-- > xval1, [xval2, ... , xval31]  pop  
-- > ival1, [ival2, ... , ival31]  pop  
--
-- csound doc: <http://www.csounds.com/manual/html/pop.html>
pop :: Tuple a =>  a
pop  = pureTuple $ return $ f 
    where f  = mopcs "pop" ((repeat Ir),[]) []

-- | 
-- Pops an f-sig frame from the global stack.
--
-- > fsig  pop_f  
--
-- csound doc: <http://www.csounds.com/manual/html/pop_f.html>
pop_f ::   Spec
pop_f  = Spec $ return $ f 
    where f  = opcs "pop_f" [(Fr,[])] []

-- | 
-- Pushes a value into the global stack.
--
-- >  push   xval1, [xval2, ... , xval31]
-- >  push   ival1, [ival2, ... , ival31]
--
-- csound doc: <http://www.csounds.com/manual/html/push.html>
push ::  [Sig] -> SE ()
push b1 = SE $ (depT_ =<<) $ lift $ f <$> mapM unSig b1
    where f a1 = opcs "push" [(Xr,(repeat Xr))] a1

-- | 
-- Pushes an f-sig frame into the global stack.
--
-- >  push_f   fsig
--
-- csound doc: <http://www.csounds.com/manual/html/push_f.html>
push_f ::  Spec -> SE ()
push_f b1 = SE $ (depT_ =<<) $ lift $ f <$> unSpec b1
    where f a1 = opcs "push_f" [(Xr,[Fr])] [a1]

-- | 
-- Initializes the stack.
--
-- Initializes and sets the size of the global stack.
--
-- >  stack   iStackSize
--
-- csound doc: <http://www.csounds.com/manual/html/stack.html>
stack ::  D -> SE ()
stack b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1
    where f a1 = opcs "stack" [(Xr,[Ir])] [a1]

-- Subinstrument Control.

-- | 
-- Creates and runs a numbered instrument instance.
--
-- Creates an instance of another instrument and is used as if it were an opcode.
--
-- > a1, [...] [, a8]  subinstr  instrnum [, p4] [, p5] [...]
-- > a1, [...] [, a8]  subinstr  "insname" [, p4] [, p5] [...]
--
-- csound doc: <http://www.csounds.com/manual/html/subinstr.html>
subinstr :: Tuple a => D -> [D] -> a
subinstr b1 b2 = pureTuple $ f <$> unD b1 <*> mapM unD b2
    where f a1 a2 = mopcs "subinstr" ((repeat Ar),[Sr] ++ (repeat Ir)) ([a1] ++ a2)

-- | 
-- Creates and runs a numbered instrument instance at init-time.
--
-- Same as subinstr, but init-time only and has no output arguments.
--
-- >  subinstrinit  instrnum [, p4] [, p5] [...]
-- >  subinstrinit  "insname" [, p4] [, p5] [...]
--
-- csound doc: <http://www.csounds.com/manual/html/subinstrinit.html>
subinstrinit ::  D -> [D] -> SE ()
subinstrinit b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> mapM unD b2
    where f a1 a2 = opcs "subinstrinit" [(Xr,(repeat Ir))] ([a1] ++ a2)

-- Time Reading.

-- | 
-- Returns the number seconds since a base date.
--
-- Returns the number seconds since a base date, using the
--       operating system's clock.  The base is 1 January 1970 for Csound
--       using doubles, and 1 January 2010 for versions using floats.
--
-- > ir  date  
--
-- csound doc: <http://www.csounds.com/manual/html/date.html>
date ::   D
date  = D $ return $ f 
    where f  = opcs "date" [(Ir,[])] []

-- | 
-- Returns as a string the date and time specified.
--
-- > Sir  dates  [ itime]
--
-- csound doc: <http://www.csounds.com/manual/html/dates.html>
dates ::   Str
dates  = Str $ return $ f 
    where f  = opcs "dates" [(Sr,[Ir])] []

-- | 
-- Reads the value of an internal clock.
--
-- > ir  readclock  inum
--
-- csound doc: <http://www.csounds.com/manual/html/readclock.html>
readclock ::  D -> D
readclock b1 = D $ f <$> unD b1
    where f a1 = opcs "readclock" [(Ir,[Ir])] [a1]

-- | 
-- Read the real time clock from the operating system.
--
-- Read the real-time clock from the operating system.
--
-- > ires  rtclock  
-- > kres  rtclock  
--
-- csound doc: <http://www.csounds.com/manual/html/rtclock.html>
rtclock ::   Sig
rtclock  = Sig $ return $ f 
    where f  = opcs "rtclock" [(Ir,[]),(Kr,[])] []

-- | 
-- Read absolute time in k-rate cycles.
--
-- Read absolute time, in k-rate cycles, since the start of an
--     	instance of an instrument. Called at both i-time as well as
--     	k-time.
--
-- > kres  timeinstk  
--
-- csound doc: <http://www.csounds.com/manual/html/timeinstk.html>
timeinstk ::   Sig
timeinstk  = Sig $ return $ f 
    where f  = opcs "timeinstk" [(Kr,[])] []

-- | 
-- Read absolute time in seconds.
--
-- Read absolute time, in seconds, since the start of an instance of an instrument.
--
-- > kres  timeinsts  
--
-- csound doc: <http://www.csounds.com/manual/html/timeinsts.html>
timeinsts ::   Sig
timeinsts  = Sig $ return $ f 
    where f  = opcs "timeinsts" [(Kr,[])] []

-- | 
-- Read absolute time in k-rate cycles.
--
-- Read absolute time, in k-rate cycles, since the start of the performance.
--
-- > ires  timek  
-- > kres  timek  
--
-- csound doc: <http://www.csounds.com/manual/html/timek.html>
timek ::   SE Sig
timek  = fmap ( Sig . return) $ SE $ (depT =<<) $ lift $ return $ f 
    where f  = opcs "timek" [(Ir,[]),(Kr,[])] []

-- | 
-- Read absolute time in seconds.
--
-- Read absolute time, in seconds, since the start of the performance.
--
-- > ires  times  
-- > kres  times  
--
-- csound doc: <http://www.csounds.com/manual/html/times.html>
times ::   SE Sig
times  = fmap ( Sig . return) $ SE $ (depT =<<) $ lift $ return $ f 
    where f  = opcs "times" [(Ir,[]),(Kr,[])] []