
first 2 bytes - initial pitch, then blocks per 3 bytes: 1b - counter, 2b - delta (some speed... need to test for understand sure). last 0 - becouse 1b counter is 0, last 2b is not writes.
dum dum dum tururum dum dum dum turururm la la la




Great that you solved the mysterySeregaZ wrote:i can see the light! shell say how it is
first 2 bytes - initial pitch, then blocks per 3 bytes: 1b - counter, 2b - delta (some speed... need to test for understand sure). last 0 - becouse 1b counter is 0, last 2b is not writes.
dum dum dum tururum dum dum dum turururm la la la


Code: Select all
Procedure.i GetOPNNote(Note.i, Pitch.i)
  
  Protected.d FreqHz, CurNote
  Protected.i BlkNum, FNum
  
  CurNote = Note + Pitch / 128
  
  FreqHz = 440 * Pow(2, (CurNote - 69) / 12)
  
  BlkNum = Note / 12 - 1
  If BlkNum < 0
    BlkNum = 0
  ElseIf BlkNum > 7
    BlkNum = 7
  EndIf  
 
  FNum = Round((144 * FreqHz / 7670454) * Pow(2, 21 - BlkNum), #PB_Round_Nearest)
  If FNum < 0
    FNum = 0
  ElseIf FNum > $7FF
    FNum = $7FF
  EndIf 
  ProcedureReturn FNum | (BlkNum * $800)
EndProcedure
Debug Hex(GetOPNNote($13+12, 0))
Debug Hex(GetOPNNote($13+12, 272))Code: Select all
Private Function GetOPNNote(ByVal Note As Byte, ByVal Pitch As Integer) As Integer
    Dim FreqHz As Double
    Dim BlkNum As Integer
    Dim FNum As Double
    Dim CurNote As Double
    
    CurNote = Note + Pitch / 128#
    
    FreqHz = 440# * 2# ^ ((CurNote - 69) / 12#)
    
    ' must be Note, not CurNote, to avoid changing octaves
    BlkNum = (Note \ 12) - 1
    If BlkNum < &H0 Then
        BlkNum = &H0
    ElseIf BlkNum > &H7 Then
        BlkNum = &H7
    End If
    'FNum = (144 * FreqHz * 2 ^ 20 / 7670454) / 2 ^ (BlkNum - 1)
    FNum = (144 * FreqHz / 7670454) * 2 ^ (21 - BlkNum)
    FNum = Int(FNum + 0.5)
    If FNum < 0 Then
        FNum = 0
    ElseIf FNum > &H7FF Then
        FNum = &H7FF
    End If
    
    GetOPNNote = FNum Or BlkNum * &H800
End Function ))))
))))

Code: Select all
  ElseIf FNum > $7FF
    FNum = $7FF
  EndIf  i try to change it... into... aaa... $34BF?
 i try to change it... into... aaa... $34BF?Code: Select all
  ret = FNum | (BlkNum * $800)
  if ret > $34BF
    ret = $34BF
  endif
  ProcedureReturn ret
 ))) how to fix this octave? i mean how to recount correct this +shift pitch?
))) how to fix this octave? i mean how to recount correct this +shift pitch? )))) so big mess in my head becouse it
)))) so big mess in my head becouse it 
 
 
 i just apply GEMS experience with pitch into this function. for this GEMS i have sure correct work combaine programm. it make rom from this code files. so i set in this code file pitch x and note n, then make rom, then start this rom at emulator of SMD, then make log file for sound chip, then read this log. that way i know pitch 256 it is +1 to note. not 128, as that procedure do.
 i just apply GEMS experience with pitch into this function. for this GEMS i have sure correct work combaine programm. it make rom from this code files. so i set in this code file pitch x and note n, then make rom, then start this rom at emulator of SMD, then make log file for sound chip, then read this log. that way i know pitch 256 it is +1 to note. not 128, as that procedure do.
Code: Select all
Procedure.i GetOPNNote(Note.i, Pitch.w)
  
  Protected.d FreqHz, CurNote, PitchCoef
  Protected.i BlkNum, FNum, CurBlkNum
  
  PitchCoef = Pitch / 256
  If PitchCoef < 1 And PitchCoef > -1
    
    If PitchCoef < 0 And (Note = 12 Or Note = 24 Or Note = 36 Or Note = 48 Or Note = 60 Or Note = 72 Or Note = 84)
      
      Note = Note - 1
      Pitch = 256 + Pitch ;(Pitch is a - value, so 256 + Pitch means 256 - Pitch) 
      
      ret = GetOPNNote(Note, Pitch)
      
    Else
      
      CurNote = Note + Pitch / 256
  
      FreqHz = 440 * Pow(2, (CurNote - 69) / 12)
  
      BlkNum = Note / 12 - 1 ; octave without pitch
      If BlkNum < 0
        BlkNum = 0
      ElseIf BlkNum > 7
        BlkNum = 7
      EndIf  
  
      FNum = Round((144 * FreqHz / 7670454) * Pow(2, 21 - BlkNum), #PB_Round_Nearest)
      If FNum < 0
        FNum = 0
      EndIf 
  
      ;count main value
      ret = FNum + (BlkNum * $800)
      
    EndIf
    
  Else
    
    Note + Pitch / 256
    Pitch - (Int(Pitch / 256) * 256)
    
    ret = GetOPNNote(Note, Pitch)
    
  EndIf
  
  ;set gems limit
  If ret > $3CBF
    ret = $3CBF
  ElseIf ret < $0142
    ret = $0142
  EndIf
  
  ProcedureReturn ret
EndProcedure but:
 but:
Code: Select all
Debug "$" + RSet(Hex(GetOPNNote($13+12, 272)), 4, "0")
Code: Select all
FNum = Round((144 * FreqHz / 7670454) * Pow(2, 21 - BlkNum), #PB_Round_Down);#PB_Round_Nearest) )))) la la la la la la la
)))) la la la la la la la now another place have uncorrect. i think it need one my round procedure... i need to remember where it is lay...
 now another place have uncorrect. i think it need one my round procedure... i need to remember where it is lay... 
 
Code: Select all
  If ReadFile(0, "C:\Games\SMD\gammatest\My\modulation_07.mod")
    startpitch.w = ReadWord(0)
    ReDim ModBlock(0)
    Repeat
      tmp.a = ReadAsciiCharacter(0)
      If tmp
        
        oldsize  = ArraySize(ModulValues())
        curpitch = ModulValues(oldsize)
        pitch    = ReadWord(0)
        ReDim ModulValues(oldsize + tmp)
        For i = oldsize To oldsize + tmp
          ModulValues(i) = curpitch + pitch * (i - oldsize)
          Debug Str(ModulValues(i)) + " " + Str(pitch)
        Next
      Else
        Break
      EndIf
    ForEver
    CloseFile(0)
  EndIfCode: Select all
Procedure Modulation(*Value)
  
  Repeat
    
    If modulationstart      
      
      tikofarray = fulllength - modulationstart
      
      FNum = GetOPNNote(note, ModulValues(tikofarray)) 
      A4 = FNum >> 8
      A0 = FNum & $FF  
      OPN_Write(0, $A4, A4)
      OPN_Write(0, $A0, A0)
      Debug Hex(FNum)
      
      modulationstart - 1
    
    EndIf
    
    Delay(80) ; let's image it as delay 1
    
  ForEver
  
EndProcedure exept that cases with $0001 difference for some times, but most values is same. and it is prototype of playing. i need to make some apply this method of playing into main code of playing. and case even worse - becouse my main playing it a little incorrect
 exept that cases with $0001 difference for some times, but most values is same. and it is prototype of playing. i need to make some apply this method of playing into main code of playing. and case even worse - becouse my main playing it a little incorrect 
 but system of note behavior very similar as modulation do - instrument for PSG it is plan of note. so i think to some how finish modulation, then start to plug PSG part.
 but system of note behavior very similar as modulation do - instrument for PSG it is plan of note. so i think to some how finish modulation, then start to plug PSG part. i am still not capture it from my head... but it is fly near
 i am still not capture it from my head... but it is fly near  i just need capture and write.
 i just need capture and write.
Code: Select all
Global Dim table(12)
table(0) = $0284
table(1) = $02AA
table(2) = $02D3
table(3) = $02FE
table(4) = $032B
table(5) = $035B
table(6) = $038E
table(7) = $03C5
table(8) = $03FE
table(9) = $043B
table(10) = $047B
table(11) = $04BF
table(12) = $0508
  Procedure.i GetFreq(note.i, pitch.w)
    note_p = pitch / 256    
    pitch = pitch - note_p * 256
    
    If pitch < 0
      note_p = note_p - 1;
      pitch = pitch + 256;
    EndIf 
    
    note = note + note_p
    If note < 0
      pitch = 0;
      note = 0 ;
    ElseIf note > 95
      note = 95
      pitch = 255      
    EndIf
    Block = note / 12
    note = note - Block * 12;
    a = table(note)
    b = table(note+1)
    FNum = a + ((b-a)*pitch)/256 + Block * 2048
    
    ProcedureReturn FNum
    
  EndProcedure same as GEMS logs file note value.
 same as GEMS logs file note value. i am not sure it is modulation problem, or it is replasing 2-3 operators of chip. now i fill registers, as they lay in a file, but probably i will need to replace 2 on 3 and 3 on 2, as some documents says.
 i am not sure it is modulation problem, or it is replasing 2-3 operators of chip. now i fill registers, as they lay in a file, but probably i will need to replace 2 on 3 and 3 on 2, as some documents says.
Code: Select all
0 Type	2 Or 3	        (02 - PSG tone, 03 - PSG noise)
1 Noise Data	[0,7]	    
2 Attack Rate	[0,$FF]	 
3 Sustain Level	[0,$F]
4 Attack Level	[0,$F]	 
5 Decay Rate	[0,$FF]	
6 Release Rate	[0,$FF]Code: Select all
;$1F - 31 - 14, 12, 10,  8,  6   4   2   0   0 
;$1E - 30 - 14, 12, 10,  8,  6,  4,  2,  0 p 0
;$1D - 29 - 14, 12, 10,  8,  6,  5,  3,  1,  0
;$1C - 28 - 14, 12, 10,  8,  7,  5,  3,  1,  0,  0
;$1B - 27 - 14, 12, 10,  9,  7,  5,  4,  2,  0,  0
;$0A - 10 - 15, 14  14  13, 12, 12, 11, 10, 10,  9,  9,  8,  7,  7,  6,  5,  5,  4,  4,  3,  2,  2,  1,  0,  0,  0
;$08 - 08 - 15  15  14  14  13  13  12  12  11  11  10  10   9   9   8  8  7  7  6  6  5  5  4  4  3  3  2  2  1  1  0
;$07 - 07 - 15  15  15  14  14  13  13  12  12  12  11  11  10  10   9  9  8  8  8  7  7  6  6  5  5  5  4  4  3  3  2  2  1  1  1  0
;$06 - 06 - 15  15  14  14  14  13  13  12  12  12  11  11  11  10  10  9  9  9  8  8  8  7  7  6  6  6  5  5  5  4  4  3  3  3  2  2  2  1  1  0
;$05 - 05 - 15  15  15  14  14  14  13  13  13  12  12  12  12
;$04 - 04 - 15  15  15  14  14  14  14  13  13  13  13  12  12  12  12  12
;$03 - 03 - 15  15  15  15  15  14  14  14  14  14  13  13  13  13  13  12  12  12  12  12  12
;$02 - 02 - 15  15  15, 15, 15, 15, 15, 14, 14, 14, 14, 14, 14, 14, 14, 13, 13, 13, 13, 13, 13, 13, 13, 12, 12, 12, 12, 12, 12, 12, 12, 11, 11, 11, 11, 11, 11, 11, 11, 11, 11, 11, 11, 11, 11, 11, 11, 
;$01 - 01 - 15  15  15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 14, 14, 14, 14, 14, 14, 14, 14, 14, 14, 14, 14, 14, 14, 14, 14, 13, 13, 13, 13, 13, 13, 13, 13, 13, 13, 13, 
 
 

 )))))) I did not expect.
)))))) I did not expect.Code: Select all
Global Dim PSGInstARValues(0)
Procedure FillARarray(ARvalue.i, ALvalue.i)
  
  ReDim PSGInstARValues(0) 
  
  If ARvalue = 32 ; 0 AR, top volume, no need to fade in
    PSGInstARValues(0) = ALvalue
  Else
    counterd.d     = 255 / (ARvalue * 16)
    countershift.d = counterd
    
    For i = 15 To ALvalue Step -1
      
      counteri = Int(countershift)
      
      If counteri > 0
        startnumarray = ArraySize(PSGInstARValues())
        ReDim PSGInstARValues(startnumarray + counteri)
        For k = startnumarray To startnumarray + counteri
          PSGInstARValues(k) = i
        Next
      EndIf
      
      countershift = countershift - counteri 
      countershift + counterd 
      
    Next
    
  EndIf
  
EndProcedure
FillARarray($1B, 0)
;FillARarray($1F, 0)
;FillARarray($0A, 0)
For i = 0 To ArraySize(PSGInstARValues())
  Debug PSGInstARValues(i)
Next
 no need to load, just play. and you can change some switchers for different effect of playing.
 no need to load, just play. and you can change some switchers for different effect of playing.
Code: Select all
Enumeration
  #Window
  
  #Gadget
  #Gadget2
  
  #Img01
  #Img02
  
  #AtRP
  #AtRG
  #AtRM
  
  #AtLP
  #AtLG
  #AtLM
  
  #DcRP
  #DcRG
  #DcRM
  
  #SyLP
  #SyLG
  #SyLM
  
  #RrRP
  #RrRG
  #RrRM
  
  #Load
  
EndEnumeration
XIncludeFile "G:\DISTR\SEREGASOFT\MIDI\SN76489 module.pb"
Global type   
Global noisedata   
Global attackrate   
Global sustainlevel 
Global attacklevel  
Global decayrate   
Global releaserate
Global psgstart ; means duration
Global psgmarker
Global PhaseOfPSG
Global curvolume = 17
Global Dim PSGnote.i($5F)
For i = 0 To $21
  PSGnote(i) = 1017
Next
;PSGnote($20) = 1017
;PSGnote($21) = 1017
PSGnote($22) = 960
PSGnote($23) = 906
PSGnote($24) = 855
PSGnote($25) = 807
PSGnote($26) = 762
PSGnote($27) = 719
PSGnote($28) = 679
PSGnote($29) = 641
PSGnote($2A) = 605
PSGnote($2B) = 571
PSGnote($2C) = 539
PSGnote($2D) = 508
PSGnote($2E) = 480
PSGnote($2F) = 453
PSGnote($30) = 428
PSGnote($31) = 404
PSGnote($32) = 381
PSGnote($33) = 360
PSGnote($34) = 339
PSGnote($35) = 320
PSGnote($36) = 302
PSGnote($37) = 285
PSGnote($38) = 269
PSGnote($39) = 254
PSGnote($3A) = 240
PSGnote($3B) = 226
PSGnote($3C) = 214
PSGnote($3D) = 202
PSGnote($3E) = 190
PSGnote($3F) = 180
PSGnote($40) = 170
PSGnote($41) = 160
PSGnote($42) = 151
PSGnote($43) = 143
PSGnote($44) = 135
PSGnote($45) = 127
PSGnote($46) = 120
PSGnote($47) = 113
PSGnote($48) = 107
PSGnote($49) = 101
PSGnote($4A) = 95
PSGnote($4B) = 90
PSGnote($4C) = 85
PSGnote($4D) = 80
PSGnote($4E) = 76
PSGnote($4F) = 71
PSGnote($50) = 67
PSGnote($51) = 64
PSGnote($52) = 60
PSGnote($53) = 57
PSGnote($54) = 53
PSGnote($55) = 50
PSGnote($56) = 47
PSGnote($57) = 45
PSGnote($58) = 42
PSGnote($59) = 40
PSGnote($5A) = 38
PSGnote($5B) = 35
PSGnote($5C) = 33
PSGnote($5D) = 32
PSGnote($5E) = 30
PSGnote($5F) = 28
Global Dim PSGInstrActionsKeyOn.i(1)
Global Dim PSGInstrActionsKeyOff.i(0)
Global Dim PSGInstARValues(0) ; Attack Rate
Global Dim PSGInstDRValues(0) ; Decoy Rate
Global Dim PSGInstRRValues(0) ; Relise Rate
;{
Macro SetBit(Var, Bit)
  Var | (Bit)
EndMacro
 
Macro ClearBit(Var, Bit)
  Var & (~(Bit))
EndMacro
Macro TestBit(Var, Bit)
  Bool(Var & (Bit))
EndMacro
 
Macro NumToBit(Num)
  (1<<(Num))
EndMacro
Macro GetBits(Var, StartPos, EndPos)
  ((Var>>(StartPos))&(NumToBit((EndPos)-(StartPos)+1)-1))
EndMacro
;}
Procedure FillARarray(ARvalue.i, ALvalue.i)
  
  ReDim PSGInstARValues(0)
  
  If ARvalue = $FF Or ARvalue = 32; 0 AR, top volume immediatly
    PSGInstARValues(0) = ALvalue
  Else
    counterd.d     = 255 / (ARvalue * 16)
    countershift.d = counterd
    
    For i = 15 To ALvalue Step -1
      
      counteri = Int(countershift)
      
      If counteri > 0
        startnumarray = ArraySize(PSGInstARValues())
        ReDim PSGInstARValues(startnumarray + counteri)
        For k = startnumarray To startnumarray + counteri
          PSGInstARValues(k) = i
        Next
      EndIf
      
      countershift = countershift - counteri ; get 0.x value
      countershift + counterd                ; 0.x + how it names...
      
    Next
    
  EndIf
  
EndProcedure
Procedure FillDRarray(DRvalue.i, ALvalue.i, SLvalue.i)
  
  ReDim PSGInstDRValues(0)
  
  If DRvalue = 32 ; Sustain Level volume immedeatly
    PSGInstDRValues(0) = SLvalue
  Else
    counterd.d     = 255 / (DRvalue * 16)
    countershift.d = counterd
    
    summoftik = SLvalue - ALvalue
    tmpval    = ALvalue
    If summoftik < 0
      summoftik = ALvalue - SLvalue
      tmpval    = SLvalue
    EndIf
    
    For i = 0 To summoftik
      
      counteri = Int(countershift)
      
      If counteri > 0
        startnumarray = ArraySize(PSGInstDRValues())
        ReDim PSGInstDRValues(startnumarray + counteri)
        For k = startnumarray To startnumarray + counteri
          PSGInstDRValues(k) = tmpval + i
        Next
      EndIf
      
      countershift = countershift - counteri
      countershift + counterd               
      
    Next
    
  EndIf
  
EndProcedure
Procedure FillRRarray(RRvalue.i)
  
  ReDim PSGInstRRValues(0)
  
  If RRvalue = 32 ; silence immediatly
    PSGInstRRValues(0) = 15
  Else
    counterd.d     = 255 / (RRvalue * 16)
    countershift.d = counterd
    
    For i = 0 To 15
      
      counteri = Int(countershift)
      
      If counteri > 0
        startnumarray = ArraySize(PSGInstRRValues())
        ReDim PSGInstRRValues(startnumarray + counteri)
        For k = startnumarray To startnumarray + counteri
          PSGInstRRValues(k) = i
        Next
      EndIf
      
      countershift = countershift - counteri
      countershift + counterd    
      
    Next
    
  EndIf
  
EndProcedure
Procedure PaintSin(volume)
  
  GrabImage(#Img01, #Img02, 1, 0, 279, 70) 
  CopyImage(#Img02, #Img01)
  If StartDrawing(ImageOutput(#Img01))
    
    Plot(278, (volume * 4)+4, RGB(0, 200, 0))
    StopDrawing()
    
    SetGadgetState(#Gadget2, ImageID(#Img01))
    
  EndIf
  
EndProcedure
Procedure PSGPlay(*Value)
  
  Repeat
    
    If psgstart > 0     
      
      ;1. Attack Phase [volume up With Attack Rate until Attack Level], 
      ;2. Decay Phase [volume down With Decay Rate until Sustain Level], 
      ;3. Sustain Phase [volume down With SustainRate Until 0]
      ;actually... no, the Sustain Rate is fixed To 0 in GEMS, so the volume 
      ;stays at its level there.
      ;Anywhere in this, a "Key Off" breaks into the 
      ;4. Release Phase [volume down With Release Rate Until 0]
      ;With "volume 0" I mean "silence" here, so For the PSG it's actually value $F
      
      
      
      ;frequency is sets. i means instrument is rule of volume in a time
      
      ;get position of sound playing
      tmppsgmarker = psgmarker - psgstart
      
      Select PhaseOfPSG
        Case 0 ; Attack Rate
          
          ;check when phase is ends    
          ;Debug tmppsgmarker
          If PSGInstARValues(tmppsgmarker) <= attacklevel
            PhaseOfPSG = 1
            startdecaytik = tmppsgmarker + 1
            
            ;set volume
            ;%1001000
            Write(144 + attacklevel)
            curvolume = attacklevel
            
          Else
            
            ;set volume
            ;%1001000
            Write(144 + PSGInstARValues(tmppsgmarker))
            curvolume = PSGInstARValues(tmppsgmarker)
            
          EndIf
          
        Case 1 ; Decay Rate
          ;check when phase is ends          
          If PSGInstDRValues(tmppsgmarker - startdecaytik) >= sustainlevel
            PhaseOfPSG = 2
            startreliserate = tmppsgmarker
            
            ;set volume
            ;%1001000
            Write(144 + sustainlevel)
            curvolume = sustainlevel
          Else
            
            ;set volume
            ;%1001000
            Write(144 + PSGInstDRValues(tmppsgmarker - startdecaytik))
            curvolume = PSGInstDRValues(tmppsgmarker - startdecaytik)
            
          EndIf          
          
      EndSelect
      
      PaintSin(curvolume)
      
      psgstart - 1 
      
    Else
      
      ;start ReliseRate - Fade out
      If curvolume < 15
        
        ;Debug "RR"
        For i = 0 To ArraySize(PSGInstRRValues())
          ;get array tik
          If PSGInstRRValues(i) >= curvolume
            startfadeout = i
            
            Write(144 + PSGInstRRValues(i))
            
            PaintSin(PSGInstRRValues(i))
            
            Break
          EndIf
        Next
        
        curvolume = 16
        
      ElseIf curvolume = 16
        
        If startfadeout <= ArraySize(PSGInstRRValues())
          
          Write(144 + PSGInstRRValues(startfadeout))
          
          PaintSin(PSGInstRRValues(startfadeout))
          
          If PSGInstRRValues(startfadeout) = 15
            curvolume = 17 ; stop RR work
          EndIf
          
          startfadeout + 1
          
        EndIf
        
      EndIf 
      
    EndIf
    
    ;Delay(80) ; let's image it as gems's delay 1. 
               ; but, as test shows, it cant be delay 1, but 1/60sec
    Delay(17)  ; 16.66666.... let it be 17
    
  ForEver
  
EndProcedure
;FillARarray($1B, 0)
;FillARarray($1F, 0)
;FillARarray($0A, 0)
;For i = 0 To ArraySize(PSGInstARValues())
;  text$ + "  " +  Str(PSGInstARValues(i))
;Next
;Debug ";         " + text$
;FillDRarray($0A, 15)
;For i = 0 To ArraySize(PSGInstDRValues())
;  text$ + "  " +  Str(PSGInstDRValues(i))
;Next
;Debug ";         " + text$
SetClock(3579545) 
If OpenWindow(#Window, 100, 200, 420, 140, "", #PB_Window_SystemMenu | #PB_Window_MinimizeGadget | #PB_Window_ScreenCentered)
  
  ;If ReadFile(0, "G:\DISTR\SEREGASOFT\MIDI\PSGinstrum\patch_0F.raw")
    ;02 00 FF 0A 09 0A 14
    ;0 Type	2 Or 3	          02               02 - PSG tone, 03 - PSG noise
    ;1 Noise Data	[0,7]	      00
    ;2 Attack Rate	[0,$FF]	  FF
    ;3 Sustain Level	[0,$F]	0A
    ;4 Attack Level	[0,$F]	  09
    ;5 Decay Rate	[0,$FF]	    0A
    ;6 Release Rate	[0,$FF]	  14 
    ;CloseFile(0)
  ;EndIf
  
  ;lets image that was read as:
  type         = 2
  noisedata    = 0
  attackrate   = $10
  sustainlevel = $05
  attacklevel  = $00
  decayrate    = $05
  releaserate  = $14
  
  FillARarray(attackrate, attacklevel)
  FillDRarray(decayrate, attacklevel, sustainlevel)
  FillRRarray(releaserate)  
  
  ButtonGadget(#Load, 10, 10, 50, 20, "load")
  
  ButtonGadget(#Gadget, 10, 40, 50, 20, "play")
  
  x = 70
  ButtonGadget(#AtRP, x+40, 10, 20, 20, "+")
  StringGadget(#AtRG, x+20, 10, 20, 20, Str(attackrate), #PB_String_Numeric | #PB_String_ReadOnly)
  ButtonGadget(#AtRM, x, 10, 20, 20, "-")
  GadgetToolTip(#AtRG, "Attack Rate")
  
  x + 70
  ButtonGadget(#AtLP, x+40, 10, 20, 20, "+")
  StringGadget(#AtLG, x+20, 10, 20, 20, Str(attacklevel), #PB_String_Numeric | #PB_String_ReadOnly)
  ButtonGadget(#AtLM, x, 10, 20, 20, "-")
  GadgetToolTip(#AtLG, "Attack Level")
  
  x + 70
  ButtonGadget(#DcRP, x+40, 10, 20, 20, "+")
  StringGadget(#DcRG, x+20, 10, 20, 20, Str(decayrate), #PB_String_Numeric | #PB_String_ReadOnly)
  ButtonGadget(#DcRM, x, 10, 20, 20, "-")
  GadgetToolTip(#DcRG, "Decay Rate")
  
  x + 70
  ButtonGadget(#SyLP, x+40, 10, 20, 20, "+")
  StringGadget(#SyLG, x+20, 10, 20, 20, Str(sustainlevel), #PB_String_Numeric | #PB_String_ReadOnly)
  ButtonGadget(#SyLM, x, 10, 20, 20, "-")
  GadgetToolTip(#SyLG, "Systain Level")
  
  x + 70
  ButtonGadget(#RrRP, x+40, 10, 20, 20, "+")
  StringGadget(#RrRG, x+20, 10, 20, 20, Str(releaserate), #PB_String_Numeric | #PB_String_ReadOnly)
  ButtonGadget(#RrRM, x, 10, 20, 20, "-")
  GadgetToolTip(#RrRG, "Relise Rate")
  
  
  
  CreateImage(#Img01, 280, 70)
  CreateImage(#Img02, 280, 70)
  ImageGadget(#Gadget2, 100, 40, 280, 70, ImageID(#Img01), #PB_Image_Border)
  
  
  CreateThread(@PSGPlay(), 123)
  
  
  Repeat
    Event = WaitWindowEvent()
    
    Select Event
      Case #PB_Event_Gadget
        EvGadget = EventGadget()
        Select EvGadget
          Case #Gadget
            ;set frequency
            ;0 ch, tone
            writevalue = %10000000 + GetBits(PSGnote($22), 0, 3)
            Write(writevalue)
            writevalue = GetBits(PSGnote($22), 4, 7)
            Write(writevalue)
            psgstart  = 60 ; duration
            psgmarker = psgstart
            PhaseOfPSG = 0 ; 0 - Attack Rate, 1 - Decay Rate, 2 - Relise Rate
          Case #Load
            tmppath$ = OpenFileRequester("enter path to RAW file", "", "RAW Files (*.raw)|*.raw;", 0)
            If tmppath$
              If FileSize(tmppath$) = 7
                If ReadFile(0, tmppath$)
                  type         = ReadAsciiCharacter(0)
                  noisedata    = ReadAsciiCharacter(0)
                  attackrate   = ReadAsciiCharacter(0)
                  sustainlevel = ReadAsciiCharacter(0)
                  attacklevel  = ReadAsciiCharacter(0)
                  decayrate    = ReadAsciiCharacter(0)
                  releaserate  = ReadAsciiCharacter(0)
                  CloseFile(0)
                  
                  If attackrate > 32
                    attackrate = 32
                  ElseIf attackrate < 1
                    attackrate = 1
                  EndIf
                  
                  If decayrate > 32
                    decayrate = 32
                  ElseIf decayrate < 1
                    decayrate = 1
                  EndIf
                  
                  If releaserate > 32
                    releaserate = 32
                  ElseIf releaserate < 1
                    releaserate = 1
                  EndIf
                  
                  FillARarray(attackrate, attacklevel)
                  FillDRarray(decayrate, attacklevel, sustainlevel)
                  FillRRarray(releaserate)
                  
                  SetGadgetText(#AtRG, Str(attackrate))
                  SetGadgetText(#SyLG, Str(sustainlevel))
                  SetGadgetText(#AtLG, Str(attacklevel))
                  SetGadgetText(#DcRG, Str(decayrate))
                  SetGadgetText(#RrRG, Str(releaserate))
                  
                EndIf
              Else
                MessageRequester("attention!", "probably it is not PSG instrument file.")
              EndIf
            EndIf
            
          Case #AtRP
            attackrate = Val(GetGadgetText(#AtRG))
            If attackrate < 32
              attackrate + 1
              FillARarray(attackrate, attacklevel)
              SetGadgetText(#AtRG, Str(attackrate))
            EndIf
            
          Case #AtRM
            attackrate = Val(GetGadgetText(#AtRG))
            If attackrate > 1
              attackrate - 1
              FillARarray(attackrate, attacklevel)
              SetGadgetText(#AtRG, Str(attackrate))
            EndIf
            
          Case #AtLP
            attacklevel = Val(GetGadgetText(#AtLG))
            If attacklevel > 0
              attacklevel - 1
              FillARarray(attackrate, attacklevel)
              FillDRarray(decayrate, attacklevel, sustainlevel)
              SetGadgetText(#AtLG, Str(attacklevel))
            EndIf
            
          Case #AtLM
            attacklevel = Val(GetGadgetText(#AtLG))
            If attacklevel < 15
              attacklevel + 1
              FillARarray(attackrate, attacklevel)
              FillDRarray(decayrate, attacklevel, sustainlevel)
              SetGadgetText(#AtLG, Str(attacklevel))
            EndIf            
            
          Case #DcRP
            decayrate = Val(GetGadgetText(#DcRG))
            If decayrate < 32
              decayrate + 1
              FillDRarray(decayrate, attacklevel, sustainlevel)              
              SetGadgetText(#DcRG, Str(decayrate))
            EndIf
            
          Case #DcRM
            decayrate = Val(GetGadgetText(#DcRG))
            If decayrate > 1
              decayrate - 1
              FillDRarray(decayrate, attacklevel, sustainlevel)   
              SetGadgetText(#DcRG, Str(decayrate))
            EndIf
            
          Case #SyLP
            sustainlevel = Val(GetGadgetText(#SyLG))
            If sustainlevel > 0
              sustainlevel - 1
              FillDRarray(decayrate, attacklevel, sustainlevel)
              SetGadgetText(#SyLG, Str(sustainlevel))
            EndIf
            
          Case #SyLM
            sustainlevel = Val(GetGadgetText(#SyLG))
            If sustainlevel < 15
              sustainlevel + 1
              FillDRarray(decayrate, attacklevel, sustainlevel)
              SetGadgetText(#SyLG, Str(sustainlevel))
            EndIf 
            
          Case #RrRP
            releaserate = Val(GetGadgetText(#RrRG))
            If releaserate < 32
              releaserate + 1
              FillRRarray(releaserate)              
              SetGadgetText(#RrRG, Str(releaserate))
            EndIf
            
          Case #RrRM
            releaserate = Val(GetGadgetText(#RrRG))
            If releaserate > 1
              releaserate - 1
              FillRRarray(releaserate)
              SetGadgetText(#RrRG, Str(releaserate))
            EndIf
            
        EndSelect
        
      Case #PB_Event_CloseWindow
        Quit = 1 
    EndSelect
    
  Until Quit = 1 
  
EndIf