-- | Other FLTK Widgets
module CsoundExpr.Opcodes.Control.FltkOther
    (flBox,
     flButBank,
     flButton,
     flKeyIn,
     flHvsBox,
     flMouse,
     flPrintk,
     flPrintk2,
     flSlidBnk,
     flSlidBnk2,
     flSlidBnkGetHandle,
     flSlidBnkSet,
     flSlidBnk2Set,
     flSlidBnk2Setk,
     flValue,
     flVslidBnk,
     flVslidBnk2,
     flXyin)
where



import CsoundExpr.Base.Types
import CsoundExpr.Base.MultiOut
import CsoundExpr.Base.SideEffect
import CsoundExpr.Base.UserDefined



-- | * opcode : FLbox
--  
--  
-- * syntax : 
--  
--  >   ihandle FLbox "label", itype, ifont, isize, iwidth, iheight, ix, iy [, image]
--  
--  
-- * description : 
--  
--  A FLTK widget that displays text inside of a box.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLbox.html>
 
flBox ::
        [Irate] ->
          String ->
            Irate ->
              Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate
flBox i0init s1label i2type i3font i4size i5width i6height i7x i8y
  = opcode "FLbox" args
  where args
          = [to s1label, to i2type, to i3font, to i4size, to i5width,
             to i6height, to i7x, to i8y]
              ++ map to i0init


-- | * opcode : FLbutBank
--  
--  
-- * syntax : 
--  
--  >   kout, ihandle FLbutBank itype, inumx, inumy, iwidth, iheight, ix, iy, 
--  >       iopcode [, kp1] [, kp2] [, kp3] [, kp4] [, kp5] [....] [, kpN]
--  
--  
-- * description : 
--  
--  A FLTK widget opcode that creates a bank of buttons.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLbutBank.html>
 
flButBank ::
            (K k0) =>
            Irate ->
              Irate ->
                Irate ->
                  Irate -> Irate -> Irate -> Irate -> Irate -> [k0] -> (Krate, Irate)
flButBank i0type i1numx i2numy i3width i4height i5x i6y i7opcode
  k8vals = mo2 $ opcode "FLbutBank" args
  where args
          = [to i0type, to i1numx, to i2numy, to i3width, to i4height,
             to i5x, to i6y, to i7opcode]
              ++ map to k8vals


-- | * opcode : FLbutton
--  
--  
-- * syntax : 
--  
--  >   kout, ihandle FLbutton "label", ion, ioff, itype, iwidth, iheight, ix, 
--  >       iy, iopcode [, kp1] [, kp2] [, kp3] [, kp4] [, kp5] [....] [, kpN]
--  
--  
-- * description : 
--  
--  A FLTK widget opcode that creates a button.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLbutton.html>
 
flButton ::
           (K k0) =>
           String ->
             Irate ->
               Irate ->
                 Irate ->
                   Irate -> Irate -> Irate -> Irate -> Irate -> [k0] -> (Krate, Irate)
flButton s0label i1on i2off i3type i4width i5height i6x i7y
  i8opcode k9vals = mo2 $ opcode "FLbutton" args
  where args
          = [to s0label, to i1on, to i2off, to i3type, to i4width,
             to i5height, to i6x, to i7y, to i8opcode]
              ++ map to k9vals


-- | * opcode : FLkeyIn
--  
--  
-- * syntax : 
--  
--  >   kascii FLkeyIn [ifn]
--  
--  
-- * description : 
--  
--  FLkeyIn informs about the status of a key pressed by the user on
-- the alphanumeric keyboard when an FLTK panel has got the focus.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLkeyIn.html>
 
flKeyIn :: [Irate] -> Krate
flKeyIn i0init = opcode "FLkeyIn" args
  where args = map to i0init


-- | * opcode : FLhvsBox
--  
--  
-- * syntax : 
--  
--  >   ihandle FLhvsBox inumlinesX, inumlinesY, iwidth, iheight, ix, iy [, image]
--  
--  
-- * description : 
--  
--  FLhvsBox displays a box with a grid useful for visualizing
-- two-dimensional Hyper Vectorial Synthesis.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLhvsBox.html>
 
flHvsBox ::
           [Irate] ->
             Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate
flHvsBox i0init i1numlinesX i2numlinesY i3width i4height i5x i6y
  = opcode "FLhvsBox" args
  where args
          = [to i1numlinesX, to i2numlinesY, to i3width, to i4height, to i5x,
             to i6y]
              ++ map to i0init


-- | * opcode : FLmouse
--  
--  
-- * syntax : 
--  
--  >   kx, ky, kb1, kb2, kb3 FLmouse [imode]
--  
--  
-- * description : 
--  
--  FLmouse returns the coordinates of the mouse position within an
-- FLTK panel and the state of the three mouse buttons.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLmouse.html>
 
flMouse :: [Irate] -> MultiOut
flMouse i0init = opcode "FLmouse" args
  where args = map to i0init


-- | * opcode : FLprintk
--  
--  
-- * syntax : 
--  
--  >   FLprintk itime, kval, idisp
--  
--  
-- * description : 
--  
--  FLprintk is similar to printk but shows values of a k-rate
-- signal in a text field instead of on the console.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLprintk.html>
 
flPrintk :: (K k0) => Irate -> k0 -> Irate -> SignalOut
flPrintk i0time k1val i2disp = outOpcode "FLprintk" args
  where args = [to i0time, to k1val, to i2disp]


-- | * opcode : FLprintk2
--  
--  
-- * syntax : 
--  
--  >   FLprintk2 kval, idisp
--  
--  
-- * description : 
--  
--  FLprintk2 is similar to FLprintk but shows a k-rate variable's
-- value only when it changes.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLprintk2.html>
 
flPrintk2 :: (K k0) => k0 -> Irate -> SignalOut
flPrintk2 k0val i1disp = outOpcode "FLprintk2" args
  where args = [to k0val, to i1disp]


-- | * opcode : FLslidBnk
--  
--  
-- * syntax : 
--  
--  >   FLslidBnk "names", inumsliders [, ioutable] [, iwidth] [, iheight] [, ix] 
--  >       [, iy] [, itypetable] [, iexptable] [, istart_index] [, iminmaxtable]
--  
--  
-- * description : 
--  
--  FLslidBnk is a widget containing a bank of horizontal sliders.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLslidBnk.html>
 
flSlidBnk :: [Irate] -> String -> Irate -> SignalOut
flSlidBnk i0init s1names i2numsliders = outOpcode "FLslidBnk" args
  where args = [to s1names, to i2numsliders] ++ map to i0init


-- | * opcode : FLslidBnk2
--  
--  
-- * syntax : 
--  
--  >   FLslidBnk2 "names", inumsliders, ioutable, iconfigtable [,iwidth, iheight, ix, iy, istart_index]
--  
--  
-- * description : 
--  
--  FLslidBnk2 is a widget containing a bank of horizontal sliders.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLslidBnk2.html>
 
flSlidBnk2 ::
             [Irate] -> String -> Irate -> Irate -> Irate -> SignalOut
flSlidBnk2 i0init s1names i2numsliders i3outable i4configtable
  = outOpcode "FLslidBnk2" args
  where args
          = [to s1names, to i2numsliders, to i3outable, to i4configtable] ++
              map to i0init


-- | * opcode : FLslidBnkGetHandle
--  
--  
-- * syntax : 
--  
--  >   ihandle FLslidBnkGetHandle
--  
--  
-- * description : 
--  
--  FLslidBnkGetHandle gets the handle of last slider bank created.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLslidBnkGetHandle.html>
 
flSlidBnkGetHandle :: Irate
flSlidBnkGetHandle = opcode "FLslidBnkGetHandle" args
  where args = []


-- | * opcode : FLslidBnkSet
--  
--  
-- * syntax : 
--  
--  >   FLslidBnkSet ihandle, ifn [, istartIndex, istartSlid, inumSlid]
--  
--  
-- * description : 
--  
--  FLslidBnkSet modifies the values of a slider bank according to
-- an array of values stored in a table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLslidBnkSet.html>
 
flSlidBnkSet :: [Irate] -> Irate -> Irate -> SignalOut
flSlidBnkSet i0init i1handle i2fn = outOpcode "FLslidBnkSet" args
  where args = [to i1handle, to i2fn] ++ map to i0init


-- | * opcode : FLslidBnk2Set
--  
--  
-- * syntax : 
--  
--  >   FLslidBnk2Set ihandle, ifn [, istartIndex, istartSlid, inumSlid]
--  
--  
-- * description : 
--  
--  FLslidBnk2Set modifies the values of a slider bank according to
-- an array of values stored in a table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLslidBnk2Set.html>
 
flSlidBnk2Set :: [Irate] -> Irate -> Irate -> SignalOut
flSlidBnk2Set i0init i1handle i2fn = outOpcode "FLslidBnk2Set" args
  where args = [to i1handle, to i2fn] ++ map to i0init


-- | * opcode : FLslidBnk2Setk
--  
--  
-- * syntax : 
--  
--  >   FLslidBnk2Setk ktrig, ihandle, ifn [, istartIndex, istartSlid, inumSlid]
--  
--  
-- * description : 
--  
--  FLslidBnk2Setk modifies the values of a slider bank according to
-- an array of values stored in a table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLslidBnk2Setk.html>
 
flSlidBnk2Setk ::
                 (K k0) => [Irate] -> k0 -> Irate -> Irate -> SignalOut
flSlidBnk2Setk i0init k1trig i2handle i3fn
  = outOpcode "FLslidBnk2Setk" args
  where args = [to k1trig, to i2handle, to i3fn] ++ map to i0init


-- | * opcode : FLvalue
--  
--  
-- * syntax : 
--  
--  >   ihandle FLvalue "label", iwidth, iheight, ix, iy
--  
--  
-- * description : 
--  
--  FLvalue shows current the value of a valuator in a text field.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLvalue.html>
 
flValue :: String -> Irate -> Irate -> Irate -> Irate -> Irate
flValue s0label i1width i2height i3x i4y = opcode "FLvalue" args
  where args = [to s0label, to i1width, to i2height, to i3x, to i4y]


-- | * opcode : FLvslidBnk
--  
--  
-- * syntax : 
--  
--  >   FLvslidBnk "names", inumsliders [, ioutable] [, iwidth] [, iheight] [, ix] 
--  >       [, iy] [, itypetable] [, iexptable] [, istart_index] [, iminmaxtable]
--  
--  
-- * description : 
--  
--  FLvslidBnk is a widget containing a bank of vertical sliders.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLvslidBnk.html>
 
flVslidBnk :: [Irate] -> String -> Irate -> SignalOut
flVslidBnk i0init s1names i2numsliders
  = outOpcode "FLvslidBnk" args
  where args = [to s1names, to i2numsliders] ++ map to i0init


-- | * opcode : FLvslidBnk2
--  
--  
-- * syntax : 
--  
--  >   FLvslidBnk2 "names", inumsliders, ioutable, iconfigtable [,iwidth, iheight, ix, iy, istart_index]
--  
--  
-- * description : 
--  
--  FLvslidBnk2 is a widget containing a bank of vertical sliders.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLvslidBnk2.html>
 
flVslidBnk2 ::
              [Irate] -> String -> Irate -> Irate -> Irate -> SignalOut
flVslidBnk2 i0init s1names i2numsliders i3outable i4configtable
  = outOpcode "FLvslidBnk2" args
  where args
          = [to s1names, to i2numsliders, to i3outable, to i4configtable] ++
              map to i0init


-- | * opcode : FLxyin
--  
--  
-- * syntax : 
--  
--  >   koutx, kouty, kinside FLxyin ioutx_min, ioutx_max, iouty_min, iouty_max, 
--  >       iwindx_min, iwindx_max, iwindy_min, iwindy_max [, iexpx, iexpy, ioutx, iouty]
--  
--  
-- * description : 
--  
--  Similar to xyin, sense the mouse cursor position in a
-- user-defined area inside an FLpanel.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLxyin.html>
 
flXyin ::
         [Irate] ->
           Irate ->
             Irate ->
               Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
flXyin i0init i1outx_min i2outx_max i3outy_min i4outy_max
  i5windx_min i6windx_max i7windy_min i8windy_max
  = opcode "FLxyin" args
  where args
          = [to i1outx_min, to i2outx_max, to i3outy_min, to i4outy_max,
             to i5windx_min, to i6windx_max, to i7windy_min, to i8windy_max]
              ++ map to i0init