module CsoundExpr.Opcodes.Control.FltkValuators
    (flCount,
     flJoy,
     flKnob,
     flRoller,
     flSlider,
     flText)
where
import CsoundExpr.Base.Types
import CsoundExpr.Base.MultiOut
import CsoundExpr.Base.SideEffect
import CsoundExpr.Base.UserDefined
 
flCount ::
          (K k0) =>
          String ->
            Irate ->
              Irate ->
                Irate ->
                  Irate -> Irate -> Irate -> Irate -> Irate -> [k0] -> (Krate, Irate)
flCount s0label i1min i2max i3step1 i4step2 i5type i6width i7height
  i8opcode k9vals = mo2 $ opcode "FLcount" args
  where args
          = [to s0label, to i1min, to i2max, to i3step1, to i4step2,
             to i5type, to i6width, to i7height, to i8opcode]
              ++ map to k9vals
 
flJoy ::
        String ->
          Irate ->
            Irate ->
              Irate ->
                Irate ->
                  Irate ->
                    Irate ->
                      Irate ->
                        Irate ->
                          Irate -> Irate -> Irate -> Irate -> (Krate, Krate, Irate, Irate)
flJoy s0label i1minx i2maxx i3miny i4maxy i5expx i6expy i7dispx
  i8dispy i9width i10height i11x i12y = mo4 $ opcode "FLjoy" args
  where args
          = [to s0label, to i1minx, to i2maxx, to i3miny, to i4maxy,
             to i5expx, to i6expy, to i7dispx, to i8dispy, to i9width,
             to i10height, to i11x, to i12y]
 
flKnob ::
         [Irate] ->
           String ->
             Irate ->
               Irate ->
                 Irate ->
                   Irate -> Irate -> Irate -> Irate -> Irate -> (Krate, Irate)
flKnob i0init s1label i2min i3max i4exp i5type i6disp i7width i8x
  i9y = mo2 $ opcode "FLknob" args
  where args
          = [to s1label, to i2min, to i3max, to i4exp, to i5type, to i6disp,
             to i7width, to i8x, to i9y]
              ++ map to i0init
 
flRoller ::
           String ->
             Irate ->
               Irate ->
                 Irate ->
                   Irate ->
                     Irate ->
                       Irate -> Irate -> Irate -> Irate -> Irate -> (Krate, Irate)
flRoller s0label i1min i2max i3step i4exp i5type i6disp i7width
  i8height i9x i10y = mo2 $ opcode "FLroller" args
  where args
          = [to s0label, to i1min, to i2max, to i3step, to i4exp, to i5type,
             to i6disp, to i7width, to i8height, to i9x, to i10y]
 
flSlider ::
           String ->
             Irate ->
               Irate ->
                 Irate ->
                   Irate ->
                     Irate -> Irate -> Irate -> Irate -> Irate -> (Krate, Irate)
flSlider s0label i1min i2max i3exp i4type i5disp i6width i7height
  i8x i9y = mo2 $ opcode "FLslider" args
  where args
          = [to s0label, to i1min, to i2max, to i3exp, to i4type, to i5disp,
             to i6width, to i7height, to i8x, to i9y]
 
flText ::
         String ->
           Irate ->
             Irate ->
               Irate ->
                 Irate -> Irate -> Irate -> Irate -> Irate -> (Krate, Irate)
flText s0label i1min i2max i3step i4type i5width i6height i7x i8y
  = mo2 $ opcode "FLtext" args
  where args
          = [to s0label, to i1min, to i2max, to i3step, to i4type,
             to i5width, to i6height, to i7x, to i8y]