- 易迪拓培训,专注于微波、射频、天线设计工程师的培养
读/写差错系数
概述
在Excel VBA中的样本程序
在HT Basic中的样本程序
概述
这个样本程序读/写差错系数。
这个程序设置测量条件、执行全2端口校准、用要写的读取差错系数预置E5071C,然后再读出该差错系数。
从E5071C读出的差错系数将以图形方式显示。
在Excel VBA中的样本程序
Sub Err_Term_Click()
Dim defrm As Long 'Session to Default Resource Manager
Dim vi As Long 'Session to instrument
Dim Ch As String
Dim CalKit As Integer
Dim Port(2) As String
Dim Result As String * 10
Dim tNop As Long
Dim Respons As String
Dim Stimulus As String
Dim ErrTerm As String
Const TimeOutTime = 40000 'timeout time.
Const Cal85032F = 4 'cal kit number
Ch = Cells(2, 6) 'Select channel
Port(1) = Cells(4, 6) 'Sets the select port 1.
Port(2) = Cells(5, 6) 'Sets the select port 2.
Respons = Cells(6, 6) 'Sets the respons port.
Stimulus = Cells(7, 6) 'Sets the stimulus port.
ErrTerm = Cells(8, 6) 'Sets the error term.
CalKit = Cal85032F 'Set cal kit (85032F)
Call viOpenDefaultRM(defrm) 'Initializes the VISA system.
Call viOpen(defrm, "GPIB0::17::INSTR", 0, 0, vi) 'Opens the session to the specified instrument.
Call viSetAttribute(vi, VI_ATTR_TMO_VALUE, TimeOutTime) 'The state of an attribute for the specified session.
Call viVPrintf(vi, "*RST" & vbLf, 0) 'Presets the setting state of the ENA.
Call viVPrintf(vi, "*CLS" & vbLf, 0) 'Clears the all status register.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:CKIT " & CalKit & vbLf, 0) 'Select the calibration kit.
Call Set_sgm_tbl(vi, Ch) 'Configures the segment table.
Select Case Cells(3, 6) 'Sets the read/write.
Case "Read"
Call Cal_Slot(vi, Ch, 2, Port) 'Full 2-Port Calibration.
Case "Write"
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COEF:METH:SOLT2 1,2" & vbLf, 0) 'Sets the calibration type to the full 2-port calibration.
End Select
Call viVPrintf(vi, ":SENS" & Ch & ":SEGM:SWE:POIN?" & vbLf, 0) 'Reads out the total number of the measurement points of all segments.
Call viVScanf(vi, "%t", Result)
Call Exec_Error_Term(vi, Ch, Val(Result), ErrTerm, Respons, Stimulus) 'Reads the error coefficient.
Call viClose(vi) 'Closes the resource manager session.
Call viClose(defrm) 'Breaks the communication and terminates the VISA system.
End
End Sub
Sub Exec_Error_Term(vi As Long, Ch As String, Nop As Long, ErrTerm As String, Respons As String, Stimulus As String)
Dim Error_Term_Data As Variant
Dim Freq_Data As Variant
Dim i As Integer, j As Integer
Dim SelMode As String
Dim Result As String * 10000
Dim RealData As Double
Dim ImagData As Double
Dim FreqData As Double
ReDim Error_Term_Data(Nop * 2) As String 'Defines the stock variables for the error coefficient as needed for NOP.
ReDim Freq_Data(Nop) As String 'Defines the stock variables for the frequency values.
SelMode = Cells(3, 6) 'Reads the read/write mode.
Select Case SelMode
Case "Read" 'Reads the error coefficient from the ena.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COEF? " & ErrTerm & "," & Respons & "," & Stimulus & vbLf, 0) 'Read the calibration coefficient data.
Call viVScanf(vi, "%t", Result)
Error_Term_Data = Split(Result, ",") 'Splits the read data by comma.
Freq_Data = Make_Freq(vi, Nop) 'Calculates the frequency values.
For i = 0 To Nop - 1
RealData = CDbl(Error_Term_Data(i * 2)) 'Reads the real data from error coefficient items.
ImagData = CDbl(Error_Term_Data(i * 2 + 1)) 'Reads the imag data from error coefficient items.
FreqData = CDbl(Freq_Data(i + 1)) 'Reads the frequency values.
Cells(10 + i, 2) = RealData 'Displays the real data to the excel sheet.
Cells(10 + i, 3) = ImagData 'Displays the imag data to the excel sheet.
Cells(10 + i, 1) = FreqData 'Displays the frequency values to the excel sheet.
Next i
Call Data_Plot(vi, Nop, ErrTerm) 'Displays the graph to the excel sheet.
Case "Write" 'Write the error coefficient to the ena.
Error_Term_Data = ErrTerm & "," & Respons & "," & Stimulus 'Sets the command parameter.
For i = 0 To Nop - 1
RealData = Cells(10 + i, 2) 'Retrieves the real data from the excel sheet.
ImagData = Cells(10 + i, 3) 'Retrieves the imag data from the excel sheet.
Error_Term_Data = Error_Term_Data & "," & RealData & "," & ImagData 'Sets the command parameter.
Next i
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COEF " & Error_Term_Data & vbLf, 0) 'Write the calibration coefficient data.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COEF:SAVE" & vbLf, 0) 'Calculates the calibration coefficients.
End Select
End Sub
Function Make_Freq(vi As Long, tPoint As Long) As Variant
Dim start_freq As Double
Dim stop_freq As Double
Dim Nop As Integer
Dim fStep As Double
Dim fPoint As Double
Dim freq_arry() As Variant
Dim MeasPoint As Integer
Const SegmentCnt = 2 'number of segment table.
ReDim freq_arry(tPoint) As Variant
MeasPoint = 1
For j = 1 To SegmentCnt
start_freq = Cells(3 + j - 1, 9) 'Sets the start frequency of segment table.
stop_freq = Cells(3 + j - 1, 10) 'Sets the stop frequency of segment table.
Nop = Cells(3 + j - 1, 13) 'Sets the nop of segment table.
fStep = (stop_freq - start_freq) / (Nop - 1) 'Calculate the frequency step.
fPoint = start_freq 'Sets the frequency start point.
For i = 1 To Nop
freq_arry(MeasPoint) = fPoint 'Sets the frequency value.
fPoint = fPoint + fStep 'Calculate the frequency points.
MeasPoint = MeasPoint + 1 'Add to measurement points.
Next i
Next j
Make_Freq = freq_arry 'Sets the frequency data array.
End Function
Sub Data_Plot(vi As Long, Nop As Long, ErrTerm As String)
Range("B10:C" & Nop + 9 & "").Select 'Select the error coefficient.
Charts.Add
ActiveChart.ChartType = xlLineStacked 'Sets the chart type.
ActiveChart.SetSourceData Source:=Sheets("Error Term").Range("A9:C" & Nop + 9 & "") 'Sets the error coefficient and displays the graph.
ActiveChart.Location Where:=xlLocationAsObject, Name:="Error Term"
ActiveChart.Axes(xlCategory).Select 'Select the formatting of X-axis.
With Selection
.TickLabelPosition = xlLow 'Displays the frequency values to low area.
End With
With ActiveChart
.HasTitle = True
.ChartTitle.Characters.Text = "Error Term " & ErrTerm 'Display the title.
End With
End Sub
Sub Set_sgm_tbl(vi As Long, Ch As String)
Dim Star1(2) As Double, Stop1(2) As Double, Pow1(2) As Double, If_bw1(2) As Double
Dim Segm As Integer, Nop1(2) As Integer, Num_of_tr1 As Integer
Dim i As Integer
Segm = 2
Star1(1) = Cells(3, 9) 'Sets the start frequency of segment 1 table.
Stop1(1) = Cells(3, 10) 'Sets the stop frequency of segment 1 table.
Pow1(1) = Cells(3, 11) 'Sets the power of segment 1 table.
If_bw1(1) = Cells(3, 12) 'Sets the ifbw of segment 1 table.
Nop1(1) = Cells(3, 13) 'Sets the nop of segment 1 table.
Star1(2) = Cells(4, 9) 'Sets the start frequency of segment 2 table.
Stop1(2) = Cells(4, 10) 'Sets the stop frequency of segment 2 table.
Pow1(2) = Cells(4, 11) 'Sets the power of segment 2 table.
If_bw1(2) = Cells(4, 12) 'Sets the ifbw of segment 2 table.
Nop1(2) = Cells(4, 13) 'Sets the nop of segment 2 table.
Call viVPrintf(vi, ":SENS" & Ch & ":SWE:TYPE SEGM" & vbLf, 0) 'Sets sweep type to segment.
Call viVPrintf(vi, ":SENS" & Ch & ":SEGM:DATA 5,0,1,1,0,0," & Segm & ",", 0) 'Sets the header of segment table.
Call viVPrintf(vi, Star1(1) & "," & Stop1(1) & "," & Nop1(1) & "," & If_bw1(1) & "," & Pow1(1) & ",", 0) 'Sets the 1st parameter.
Call viVPrintf(vi, Star1(2) & "," & Stop1(2) & "," & Nop1(2) & "," & If_bw1(2) & "," & Pow1(2) & vbLf, 0) 'Sets the 2nd parameter.
Call ErrorCheck(vi) 'Checking the error.
End Sub
Sub Cal_Slot(vi As Long, Ch As String, NumPort As String, Port() As String)
Dim Dummy
Dim i As Integer, j As Integer
Select Case NumPort
Case 1
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:METH:SOLT" & NumPort & " " & Port(1) & vbLf, 0) 'Set the 1-port calibration type.
Case 2
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:METH:SOLT" & NumPort & " " & Port(1) & "," & Port(2) & vbLf, 0) 'Set the full 2-port calibration type.
Case 3
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:METH:SOLT" & NumPort & " " & Port(1) & "," & Port(2) & "," & Port(3) & vbLf, 0) 'Set the full 3-port calibration type.
Case 4
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:METH:SOLT4 1,2,3,4" & vbLf, 0) 'Set the full 4-port calibration type.
End Select
'Reflection
For i = 1 To NumPort
MsgBox ("Set Open to Port " & Port(i) & ". then click [OK] button") 'Display the message box.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:OPEN " & Port(i) & vbLf, 0) 'Measurement the OPEN calibration.
Call viVQueryf(vi, "*OPC?" & vbLf, "%t", Dummy) 'Reads the *OPC? result.
MsgBox ("Set Short to Port " & Port(i) & ". then click [OK] button") 'Display the message box.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:SHORT " & Port(i) & vbLf, 0) 'Measurement the SHORT calibration.
Call viVQueryf(vi, "*OPC?" & vbLf, "%t", Dummy) 'Reads the *OPC? result.
MsgBox ("Set Load to Port " & Port(i) & ". then click [OK] button") 'Display the message box.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:LOAD " & Port(i) & vbLf, 0) 'Measurement the LOAD calibration.
Call viVQueryf(vi, "*OPC?" & vbLf, "%t", Dummy) 'Reads the *OPC? result.
Next i
'Transmission
For i = 1 To NumPort - 1
For j = i + 1 To NumPort
MsgBox ("Set Thru to Port " & Port(i) & "&" & Port(j) & ". then click [OK] button") 'Display the message box.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:THRU " & Port(i) & "," & Port(j) & vbLf, 0) 'Measurement the THRU calibration.
Call viVQueryf(vi, "*OPC?" & vbLf, "%t", Dummy) 'Reads the *OPC? result.
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:THRU " & Port(j) & "," & Port(i) & vbLf, 0) 'Measurement the THRU calibration.
Call viVQueryf(vi, "*OPC?" & vbLf, "%t", Dummy) 'Reads the *OPC? result.
Next j
Next i
Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:SAVE" & vbLf, 0) 'Calculating the calibration coefficients.
Call ErrorCheck(vi) 'Checking the error.
End Sub
Sub ErrorCheck(vi As Long)
Dim err As String * 50, ErrNo As Variant, Response
Call viVQueryf(vi, ":SYST:ERR?" & vbLf, "%t", err) 'Reads error message.
ErrNo = Split(err, ",") 'Gets the error code.
If Val(ErrNo(0)) <> 0 Then
Response = MsgBox(CStr(ErrNo(1)), vbOKOnly) 'Display the message box.
End If
End Sub
在HT Basic中的样本程序(ErrTerm.htb)
2000 Main:!
2010 INTEGER Agte507x,Ii,Nop
2020 INTEGER Respons,Stimulas
2030 INTEGER Port(1:2)
2040 REAL Stok(12,1:5000)
2050 REAL Stok2(12,1:5000)
2060 REAL Stok3(12,1:5000)
2070 DIM Ch$[10],Wk$[128]
2080 !
2090 ! PC's Monitor Clear
2100 CLEAR SCREEN
2110 GINIT
2130 !
2140 ! Set ENA++'s Addr
2150 Agte507x=717
2160 !
2170 Ch$="1"
2180 !
2190 ! Set ENA++'s I/O Path
2200 ASSIGN @Agte507x TO Agte507x
2210 !
2220 ON TIMEOUT SC(@Agte507x),15 RECOVER Tout
2230 !
2240 ! Set Start Port and End Port
2250 Port(1)=1
2260 Port(2)=2
2270 !
2280 ! Setup Segment Table
2290 CALL Set_sgm_tbl(@Agte507x)
2300 !
2310 ! Select Cal Kit
2320 CALL Select_cal_kit(@Agte507x,Ch$)
2330 !
2340 ! Execute Full-2Port Calibration
2350 CALL Cal_solt(@Agte507x,Ch$,2,Port(*))
2360 !
2370 ! Get All Segment's Points
2380 CALL Get_nop(@Agte507x,Nop,Ch$)
2390 !
2400 REDIM Stok(12,1:Nop*2)
2410 REDIM Stok2(12,1:Nop*2)
2420 REDIM Stok3(12,1:Nop*2)
2430 !
2440 CALL Exec_error_term(@Agte507x,"READ","ES",Ch$,1,Nop,1,1,Stok(*))
2450 CALL Exec_error_term(@Agte507x,"READ","ES",Ch$,2,Nop,2,2,Stok(*))
2460 CALL Exec_error_term(@Agte507x,"READ","ER",Ch$,3,Nop,1,1,Stok(*))
2470 CALL Exec_error_term(@Agte507x,"READ","ER",Ch$,4,Nop,2,2,Stok(*))
2480 CALL Exec_error_term(@Agte507x,"READ","ED",Ch$,5,Nop,1,1,Stok(*))
2490 CALL Exec_error_term(@Agte507x,"READ","ED",Ch$,6,Nop,2,2,Stok(*))
2500 !
2510 CALL Exec_error_term(@Agte507x,"READ","EL",Ch$,7,Nop,1,2,Stok(*))
2520 CALL Exec_error_term(@Agte507x,"READ","EL",Ch$,8,Nop,2,1,Stok(*))
2530 CALL Exec_error_term(@Agte507x,"READ","ET",Ch$,9,Nop,1,2,Stok(*))
2540 CALL Exec_error_term(@Agte507x,"READ","ET",Ch$,10,Nop,2,1,Stok(*))
2550 !
2560 CLEAR SCREEN
2570 PRINT "Push [Preset] - OK of ENA. Then push [Enter] key."
2580 INPUT "",Wk$
2590 !
2600 CALL Set_sgm_tbl(@Agte507x)
2610 !
2620 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COEF:METH:SOLT2 ";Port(1);",";Port(2)
2630 !
2640 CALL Exec_error_term(@Agte507x,"WRITE","ES",Ch$,1,Nop,1,1,Stok(*))
2650 CALL Exec_error_term(@Agte507x,"WRITE","ES",Ch$,2,Nop,2,2,Stok(*))
2660 CALL Exec_error_term(@Agte507x,"WRITE","ER",Ch$,3,Nop,1,1,Stok(*))
2670 CALL Exec_error_term(@Agte507x,"WRITE","ER",Ch$,4,Nop,2,2,Stok(*))
2680 CALL Exec_error_term(@Agte507x,"WRITE","ED",Ch$,5,Nop,1,1,Stok(*))
2690 CALL Exec_error_term(@Agte507x,"WRITE","ED",Ch$,6,Nop,2,2,Stok(*))
2700 !
2710 CALL Exec_error_term(@Agte507x,"WRITE","EL",Ch$,7,Nop,1,2,Stok(*))
2720 CALL Exec_error_term(@Agte507x,"WRITE","EL",Ch$,8,Nop,2,1,Stok(*))
2730 CALL Exec_error_term(@Agte507x,"WRITE","ET",Ch$,9,Nop,1,2,Stok(*))
2740 CALL Exec_error_term(@Agte507x,"WRITE","ET",Ch$,10,Nop,2,1,Stok(*))
2750 !
2760 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COEF:SAVE"
2770 !
2780 CALL Exec_error_term(@Agte507x,"READ","ES",Ch$,1,Nop,1,1,Stok2(*))
2790 CALL Exec_error_term(@Agte507x,"READ","ES",Ch$,2,Nop,2,2,Stok2(*))
2800 CALL Exec_error_term(@Agte507x,"READ","ER",Ch$,3,Nop,1,1,Stok2(*))
2810 CALL Exec_error_term(@Agte507x,"READ","ER",Ch$,4,Nop,2,2,Stok2(*))
2820 CALL Exec_error_term(@Agte507x,"READ","ED",Ch$,5,Nop,1,1,Stok2(*))
2830 CALL Exec_error_term(@Agte507x,"READ","ED",Ch$,6,Nop,2,2,Stok2(*))
2840 !
2850 CALL Exec_error_term(@Agte507x,"READ","EL",Ch$,7,Nop,1,2,Stok2(*))
2860 CALL Exec_error_term(@Agte507x,"READ","EL",Ch$,8,Nop,2,1,Stok2(*))
2870 CALL Exec_error_term(@Agte507x,"READ","ET",Ch$,9,Nop,1,2,Stok2(*))
2880 CALL Exec_error_term(@Agte507x,"READ","ET",Ch$,10,Nop,2,1,Stok2(*))
2890 !
2900 ASSIGN @Agte507x TO *
2910 !
2920 DISP CHR$(139)&" Done ..."&CHR$(136)
2930 STOP
2940 !
2950 Tout: OFF TIMEOUT SC(@Agte507x)
2960 !
2970 ASSIGN @Agte507x TO *
2980 !
2990 PRINT CHR$(137)&" ENA Timeout ..."&CHR$(136)
3000 END
3010!
3020 Set_sgm_tbl: SUB Set_sgm_tbl(@Agte507x)
3030 REAL Star1(1:2),Stop1(1:2),Pow1(1:2)
3040 INTEGER Segm,Nop1(1:2),Num_of_tr1
3050 INTEGER I
3060 !
3070 CLEAR SCREEN
3080 DISP CHR$(138)&" Wait ..."&CHR$(136)
3090 !
3100 Segm=2 ! Number of Segment Ch.1 : 2
3110 Star1(1)=3.E+6 ! Start Frequency Ch.1 Segm.1: 3.0 MHz
3120 Star1(2)=5.0E+7 ! Segm.2: 50.0 MHz
3130 Stop1(1)=1.0E+7 ! Stop Frequency Ch.1 Segm.1: 10.0 MHz
3140 Stop1(2)=8.E+9 ! Segm.2: 8.0 GHz
3150 Nop1(1)=2 ! Number Ch.1 Segm.1: 2
3160 Nop1(2)=170 ! of Points Segm.2: 170
3170 If_bw1(1)=7.0E+4 ! IF Bandwidth Ch.1 Segm.1: 70 kHz
3180 If_bw1(2)=7.0E+4 ! Segm.2: 70 kHz
3190 Pow1(1)=0 ! Power Ch.1 Segm.1: 0 dBm
3200 Pow1(2)=0 ! Segm.2: 0 dBm
3210 !
3220 OUTPUT @Agte507x;":SYST:PRES"
3230 !
3240 WAIT 5
3250 !
3260 ! Channel 1
3270 !
3280 OUTPUT @Agte507x;":SENS1:SWE:TYPE SEGM"
3290 OUTPUT @Agte507x;":SENS1:SEGM:DATA 5,0,1,1,0,0,";Segm;",";
3300 FOR I=1 TO Segm-1
3310 OUTPUT @Agte507x;Star1(I);",";Stop1(I);",";Nop1(I);",";If_bw1(I);",";Pow1(I);",";
3320 NEXT I
3330 OUTPUT @Agte507x;Star1(Segm);",";Stop1(Segm);",";Nop1(Segm);",";If_bw1(Segm);",";Pow1(Segm)
3340 !
3350 OUTPUT @Agte507x;":CALC1:PAR:COUN ";Num_of_tr1
3360 FOR I=1 TO Num_of_tr1
3370 OUTPUT @Agte507x;":CALC1:PAR"&VAL$(I)&":SEL"
3380 NEXT I
3390 SUBEND
3400!
3410 Select_cal_kit: SUB Select_cal_kit(@Agte507x,Ch$)
3420 !=============================================
3430 ! Calibration Kit Selection Function
3440 !=============================================
3450 !
3460 DIM Cal_kit_lbl$(1:10)[20],Inp_char$[9]
3470 DIM Msg$[80],Wk$[10]
3480 INTEGER Cal_kit,I,Noc
3490 !
3500 ! PC's Monitor Clear
3510 CLEAR SCREEN
3520 !
3530 ! Number of Cal Kid
3540 Noc=10
3550 !
3560 FOR I=1 TO Noc
3570 OUTPUT @Agte507x;":SENS1:CORR:COLL:CKIT ";I
3580 OUTPUT @Agte507x;":SENS1:CORR:COLL:CKIT:LAB?"
3590 ENTER @Agte507x;Cal_kit_lbl$(I)
3600 NEXT I
3610 ON ERROR GOTO Kit_select
3620 !
3630 PRINT "## Calibration Kit Selection ##"
3640 FOR I=1 TO Noc
3650 PRINT USING "X,2D,A,X,20A";I,":",Cal_kit_lbl$(I)
3660 NEXT I
3670 PRINT ""
3680 PRINT "Input 1 to "&VAL$(Noc)
3690 !
3700 Msg$="Input number? (1 to "&VAL$(Noc)&") "
3710 LOOP
3720 LOOP
3730 DISP Msg$;
3740 INPUT Inp_char$
3750 Cal_kit=IVAL(Inp_char$,10)
3760 EXIT IF 1<=Cal_kit AND Cal_kit<=Noc
3770 Kit_select:!
3780 BEEP
3790 END LOOP
3800 !
3810 Wk$=""
3820 PRINT TABXY(1,Cal_kit+1);
3830 PRINT USING "X,B,2D,A,X,20A,B";139,Cal_kit,":",Cal_kit_lbl$(Cal_kit),136
3840 INPUT "Sure ? [Y/N]",Wk$
3850 EXIT IF (UPC$(Wk$)="Y")
3860 PRINT TABXY(1,Cal_kit+1);
3870 PRINT USING "X,2D,A,X,20A";Cal_kit,":",Cal_kit_lbl$(Cal_kit)
3880 BEEP
3890 BEEP
3900 END LOOP
3910 OFF ERROR
3920 !
3930 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:CKIT ";Cal_kit
3940 SUBEND
3950!
3960 Cal_solt: SUB Cal_solt(@Agte507x,Ch$,INTEGER Num_of_ports,INTEGER Port(*))
3970 !=============================================
3980 ! Full n Port Calibration Function
3990 !=============================================
4000 !
4010 DIM Buff$[9]
4020 INTEGER I,J
4030 !
4040 ! PC's Monitor Clear
4050 CLEAR SCREEN
4060 !
4070 PRINT "## Full "&VAL$(Num_of_ports)&" Port Calibration ##"
4080 !
4090 ! Calibration Type Selection
4100 !
4110 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:METH:SOLT"&VAL$(Num_of_ports)&" ";
4120 FOR I=1 TO Num_of_ports-1
4130 OUTPUT @Agte507x;Port(I);",";
4140 NEXT I
4150 OUTPUT @Agte507x;Port(Num_of_ports)
4160 !
4170 ! Reflection Measurement
4180 !
4190 FOR I=1 TO Num_of_ports
4200 PRINT "Set OPEN to Port "&VAL$(Port(I))&". Then push [Enter] key."
4210 INPUT "",Buff$
4220 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:OPEN ";Port(I)
4230 OUTPUT @Agte507x;"*OPC?"
4240 ENTER @Agte507x;Buff$
4250 PRINT "Set SHORT to Port "&VAL$(Port(I))&". Then push [Enter] key."
4260 INPUT "",Buff$
4270 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:SHOR ";Port(I)
4280 OUTPUT @Agte507x;"*OPC?"
4290 ENTER @Agte507x;Buff$
4300 PRINT "Set LOAD to Port "&VAL$(Port(I))&". Then push [Enter] key."
4310 INPUT "",Buff$
4320 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:LOAD ";Port(I)
4330 OUTPUT @Agte507x;"*OPC?"
4340 ENTER @Agte507x;Buff$
4350 NEXT I
4360 !
4370 ! Transmission Measurement
4380 !
4390 FOR I=1 TO Num_of_ports-1
4400 FOR J=I+1 TO Num_of_ports
4410 PRINT "Set THRU between Port "&VAL$(Port(I))&" and Port "&VAL$(Port(J))&". Then push [Enter] key."
4420 INPUT "",Buff$
4430 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:THRU ";Port(I);",";Port(J)
4440 OUTPUT @Agte507x;"*OPC?"
4450 ENTER @Agte507x;Buff$
4460 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:THRU ";Port(J);",";Port(I)
4470 OUTPUT @Agte507x;"*OPC?"
4480 ENTER @Agte507x;Buff$
4490 NEXT J
4500 NEXT I
4510 !
4520 ! Done
4530 !
4540 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:SAVE"
4550 PRINT "Done"
4560 SUBEND
4570!
4580 Get_nop: SUB Get_nop(@Agte507x,INTEGER Nop,Ch$)
4590 ! Get All Segment's Points
4600 OUTPUT @Agte507x;":SENS"&Ch$&":SEGM:SWE:POIN?"
4610 ENTER @Agte507x;Nop
4620 SUBEND
4630 Exec_error_term: SUB Exec_error_term(@Agte507x,Rw$,Id$,Ch$,INTEGER Idx,Nop,Respons,Stimulas,REAL Stok(*))
4640 INTEGER Ii
4650 REAL Error_term_data(1:5000)
4660 !
4670 DISP CHR$(138)&" Wait ..."&CHR$(136)
4680 !
4690 REDIM Error_term_data(1:Nop*2)
4700 !
4710 SELECT Rw$
4720 CASE "WRITE"
4730 FOR Ii=1 TO Nop
4740 Error_term_data(2*Ii-1)=Stok(Idx,2*Ii-1)
4750 Error_term_data(2*Ii)=Stok(Idx,2*Ii)
4760 NEXT Ii
4770 !
4780 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COEF "&Id$&",";Respons;",";Stimulas;",";Error_term_data(*)
4790 !
4800 CASE "READ"
4810 FOR Ii=1 TO Nop
4820 Error_term_data(2*Ii-1)=-999
4830 Error_term_data(2*Ii)=-999
4840 NEXT Ii
4850 !
4860 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COEF? "&Id$&",";Respons;",";Stimulas
4870 ENTER @Agte507x;Error_term_data(*)
4880 !
4890 CALL Data_plot(Id$,Respons,Stimulas,Nop,Error_term_data(*))
4900 !
4910 FOR Ii=1 TO Nop
4920 Stok(Idx,2*Ii-1)=Error_term_data(2*Ii-1)
4930 Stok(Idx,2*Ii)=Error_term_data(2*Ii)
4940 NEXT Ii
4950 !
4960 END SELECT
4970 SUBEND
4980!
4990 Data_plot: SUB Data_plot(Error_term$,INTEGER Respons,Stimulas,Nop,REAL Error_term_data(*))
5000 INTEGER Ii,Pen(1:2)
5010 REAL Y_minmax(1:2)
5020 DIM Wk$[20]
5030 !
5040 CLEAR SCREEN
5050 GINIT
5060 GCLEAR
5070 !
5080 Pen(1)=3
5090 Pen(2)=4
5100 !
5110 ! Get Min Value and Max Value from all data
5120 Y_minmax(1)=MIN(Error_term_data(*))
5130 Y_minmax(2)=MAX(Error_term_data(*))
5150 !
5160 IF (Y_minmax(1)=Y_minmax(2)) AND (Y_minmax(1)=0) THEN
5170 Y_minmax(1)=1
5180 Y_minmax(2)=-1
5190 ELSE
5200 IF (Y_minmax(1)=Y_minmax(2)) THEN
5210 Y_minmax(1)=Y_minmax(1)*.5
5220 Y_minmax(2)=Y_minmax(2)*1.5
5230 END IF
5240 END IF
5250 !
5260 VIEWPORT 25*RATIO,80*RATIO,40,90
5270 WINDOW 1,Nop,Y_minmax(1),Y_minmax(2)
5280 FRAME
5290 !
5300 VIEWPORT 80*RATIO,100*RATIO,40,90
5310 WINDOW 0,2,0,2
5320 PEN Pen(1)
5330 CSIZE 2.5
5340 LORG 2
5350 MOVE .2,1.5
5360 DRAW .4,1.5
5370 MOVE .5,1.5
5380 PEN 1
5390 LABEL ":Real Value"
5400 !
5410 PEN Pen(2)
5420 MOVE .2,1
5430 DRAW .4,1
5440 MOVE .5,1
5450 PEN 1
5460 LABEL ":Image Value"
5470 !
5480 VIEWPORT 25*RATIO,80*RATIO,90,100
5490 WINDOW 0,2,0,2
5500 CSIZE 3
5510 LORG 5
5520 MOVE 1,1.2
5530 LABEL "Error Term:"&Error_term$
5540 !
5550 MOVE 1,.5
5560 LABEL "Respons Port:"&VAL$(Respons)&" Stimulas Port:"&VAL$(Stimulas)
5570 !
5580 VIEWPORT 0,25*RATIO,40,90
5590 WINDOW 0,2,0,2
5600 CLIP -10,10,-10,10
5610 LORG 8
5620 CSIZE 3
5630 !
5640 MOVE 1.9,0
5650 LABEL VAL$(Y_minmax(1))
5660 MOVE 1.9,2
5670 LABEL VAL$(Y_minmax(2))
5680 !
5690 VIEWPORT 25*RATIO,80*RATIO,30,40
5700 WINDOW 0,2,0,2
5710 CLIP -10,10,-10,10
5720 LORG 5
5730 MOVE 0,1.5
5740 LABEL VAL$(1)
5750 MOVE 2,1.5
5760 LABEL VAL$(Nop)
5770 !
5780 VIEWPORT 25*RATIO,80*RATIO,40,90
5790 WINDOW 1,Nop,Y_minmax(1),Y_minmax(2)
5800 FOR Ii=2 TO Nop
5820 PEN Pen(1)
5830 MOVE Ii-1,Error_term_data(2*(Ii-1)-1)
5840 DRAW Ii,Error_term_data(2*Ii-1)
5860 !
5870 PEN Pen(2)
5880 MOVE Ii-1,Error_term_data(2*(Ii-1))
5890 DRAW Ii,Error_term_data(2*Ii)
5900 NEXT Ii
5910 !
5920 PEN 1
5930 BEEP
5940 INPUT "Cont:push [Enter] key",Wk$
5950 SUBEND
5960!
上一篇:样本程序
下一篇:读出二进制格式的数据