-- | FLTK Widgets and GUI controllers
module CsoundExpr.Opcodes.Control.FltkIntro
    (flRun,
     flGetsnap,
     flLoadsnap,
     flSavesnap,
     flSetsnap,
     flSetSnapGroup,
     flGroup,
     flGroupEnd,
     flPack,
     flPackEnd,
     flPanel,
     flPanelEnd,
     flScroll,
     flScrollEnd,
     flTabs,
     flTabsEnd)
where



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



-- | * opcode : FLrun
--  
--  
-- * syntax : 
--  
--  >   FLrun
--  
--  
-- * description : 
--  
--  Starts the FLTK widget thread.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLrun.html>
 
flRun :: SignalOut
flRun = outOpcode "FLrun" args
  where args = []


-- | * opcode : FLgetsnap
--  
--  
-- * syntax : 
--  
--  >   inumsnap FLgetsnap index [, igroup]
--  
--  
-- * description : 
--  
--  Retrieves a previously stored snapshot (in memory), i.e. sets
-- all valuator to the corresponding values stored in that snaphot.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLgetsnap.html>
 
flGetsnap :: [Irate] -> Irate -> Irate
flGetsnap i0init i1ndex = opcode "FLgetsnap" args
  where args = [to i1ndex] ++ map to i0init


-- | * opcode : FLloadsnap
--  
--  
-- * syntax : 
--  
--  >   FLloadsnap "filename" [, igroup]
--  
--  
-- * description : 
--  
--  FLloadsnap loads all the snapshots contained in a file into the
-- memory bank of the current orchestra.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLloadsnap.html>
 
flLoadsnap :: [Irate] -> String -> SignalOut
flLoadsnap i0init s1filename = outOpcode "FLloadsnap" args
  where args = [to s1filename] ++ map to i0init


-- | * opcode : FLsavesnap
--  
--  
-- * syntax : 
--  
--  >   FLsavesnap "filename" [, igroup]
--  
--  
-- * description : 
--  
--  FLsavesnap saves all snapshots currently created (i.e. the
-- entire memory bank) into a file.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLsavesnap.html>
 
flSavesnap :: [Irate] -> String -> SignalOut
flSavesnap i0init s1filename = outOpcode "FLsavesnap" args
  where args = [to s1filename] ++ map to i0init


-- | * opcode : FLsetsnap
--  
--  
-- * syntax : 
--  
--  >   inumsnap, inumval FLsetsnap index [, ifn, igroup]
--  
--  
-- * description : 
--  
--  FLsetsnap stores the current status of all valuators present in
-- the orchestra into a snapshot location (in memory).
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLsetsnap.html>
 
flSetsnap :: [Irate] -> Irate -> MultiOut
flSetsnap i0init i1ndex = opcode "FLsetsnap" args
  where args = [to i1ndex] ++ map to i0init


-- | * opcode : FLsetSnapGroup
--  
--  
-- * syntax : 
--  
--  >   FLsetSnapGroup igroup
--  
--  
-- * description : 
--  
--  FLsetSnapGroup determines the snapshot group of valuators
-- declared after it.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLsetSnapGroup.html>
 
flSetSnapGroup :: Irate -> SignalOut
flSetSnapGroup i0group = outOpcode "FLsetSnapGroup" args
  where args = [to i0group]


-- | * opcode : FLgroup
--  
--  
-- * syntax : 
--  
--  >   FLgroup "label", iwidth, iheight, ix, iy [, iborder] [, image]
--  
--  
-- * description : 
--  
--  A FLTK container opcode that groups child widgets.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLgroup.html>
 
flGroup ::
          [Irate] -> String -> Irate -> Irate -> Irate -> Irate -> SignalOut
flGroup i0init s1label i2width i3height i4x i5y
  = outOpcode "FLgroup" args
  where args
          = [to s1label, to i2width, to i3height, to i4x, to i5y] ++
              map to i0init


-- | * opcode : FLgroupEnd
--  
--  
-- * syntax : 
--  
--  >   FLgroupEnd
--  
--  
-- * description : 
--  
--  Marks the end of a group of FLTK child widgets.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLgroupEnd.html>
 
flGroupEnd :: SignalOut
flGroupEnd = outOpcode "FLgroupEnd" args
  where args = []


-- | * opcode : FLpack
--  
--  
-- * syntax : 
--  
--  >   FLpack iwidth, iheight, ix, iy, itype, ispace, iborder
--  
--  
-- * description : 
--  
--  FLpack provides the functionality of compressing and aligning
-- widgets.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLpack.html>
 
flPack ::
         Irate ->
           Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> SignalOut
flPack i0width i1height i2x i3y i4type i5space i6border
  = outOpcode "FLpack" args
  where args
          = [to i0width, to i1height, to i2x, to i3y, to i4type, to i5space,
             to i6border]


-- | * opcode : FLpackEnd
--  
--  
-- * syntax : 
--  
--  >   FLpackEnd
--  
--  
-- * description : 
--  
--  Marks the end of a group of compressed or aligned FLTK widgets.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLpackEnd.html>
 
flPackEnd :: SignalOut
flPackEnd = outOpcode "FLpackEnd" args
  where args = []


-- | * opcode : FLpanel
--  
--  
-- * syntax : 
--  
--  >   FLpanel "label", iwidth, iheight [, ix] [, iy] [, iborder] [, ikbdcapture] [, iclose]
--  
--  
-- * description : 
--  
--  Creates a window that contains FLTK widgets.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLpanel.html>
 
flPanel :: [Irate] -> String -> Irate -> Irate -> SignalOut
flPanel i0init s1label i2width i3height = outOpcode "FLpanel" args
  where args = [to s1label, to i2width, to i3height] ++ map to i0init


-- | * opcode : FLpanelEnd
--  
--  
-- * syntax : 
--  
--  >   FLpanelEnd
--  
--  
-- * description : 
--  
--  Marks the end of a group of FLTK widgets contained inside of a
-- window (panel).
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLpanelEnd.html>
 
flPanelEnd :: SignalOut
flPanelEnd = outOpcode "FLpanelEnd" args
  where args = []


-- | * opcode : FLscroll
--  
--  
-- * syntax : 
--  
--  >   FLscroll iwidth, iheight [, ix] [, iy]
--  
--  
-- * description : 
--  
--  FLscroll adds scroll bars to an area.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLscroll.html>
 
flScroll :: [Irate] -> Irate -> Irate -> SignalOut
flScroll i0init i1width i2height = outOpcode "FLscroll" args
  where args = [to i1width, to i2height] ++ map to i0init


-- | * opcode : FLscrollEnd
--  
--  
-- * syntax : 
--  
--  >   FLscrollEnd
--  
--  
-- * description : 
--  
--  A FLTK opcode that marks the end of an area with scrollbars.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLscrollEnd.html>
 
flScrollEnd :: SignalOut
flScrollEnd = outOpcode "FLscrollEnd" args
  where args = []


-- | * opcode : FLtabs
--  
--  
-- * syntax : 
--  
--  >   FLtabs iwidth, iheight, ix, iy
--  
--  
-- * description : 
--  
--  FLtabs is a file card tabs interface that is useful to display
-- several areas containing widgets in the same windows,
-- alternatively. It must be used together with FLgroup, another
-- container that groups child widgets.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLtabs.html>
 
flTabs :: Irate -> Irate -> Irate -> Irate -> SignalOut
flTabs i0width i1height i2x i3y = outOpcode "FLtabs" args
  where args = [to i0width, to i1height, to i2x, to i3y]


-- | * opcode : FLtabsEnd
--  
--  
-- * syntax : 
--  
--  >   FLtabsEnd
--  
--  
-- * description : 
--  
--  Marks the end of a tabbed FLTK interface.
--  
--  
-- * url : <http://www.csounds.com/manual/html/FLtabsEnd.html>
 
flTabsEnd :: SignalOut
flTabsEnd = outOpcode "FLtabsEnd" args
  where args = []