校准

E5071C

校准

有关样本程序的其他主题

概述

样本程序执行指定校准类型的校准。

有关此程序的详情,请参见校准

在Excel VBA中的样本程序

Sub Cal_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(4) As String

    

    Const TimeOutTime = 40000   'timeout time.

    Const Cal85032F = 4         'cal kit number.

    

    Ch = Cells(5, 5)            'Select channel

    Port(1) = Cells(3, 6)       'Sets the select port 1.

    Port(2) = Cells(3, 7)       'Sets the select port 2.

    Port(3) = Cells(3, 8)       'Sets the select port 3.

    Port(4) = Cells(3, 9)       'Sets the select port 4.

    CalKit = Cal85032F          'Sets 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

    

    Select Case Cells(3, 5)

        Case "Response (Open)"   'Perform response calibration (OPEN).

            Call Cal_Resp(vi, Ch, "OPEN", Port(1))

        Case "Response (Short)"   'Perform response calibration (SHORT).

            Call Cal_Resp(vi, Ch, "Short", Port(1))

        Case "Response (Thru)"    'Perform response calibration (Thru).

            Call Cal_RespThru(vi, Ch, "Thru", Port(1), Port(2))

        Case "Full 1 Port"    'Perform 1-port calibration.

            Call Cal_Slot(vi, Ch, 1, Port)

        Case "Full 2 Port"     'Perform full 2-port calibration.

            Call Cal_Slot(vi, Ch, 2, Port)

        Case "Full 3 Port"     'Perform full 3-port calibration.

            Call Cal_Slot(vi, Ch, 3, Port)

        Case "Full 4 Port"    'Perform full 4-port calibration.

            Call Cal_Slot(vi, Ch, 4, Port)

    End Select

    

    Call viClose(vi)  'Closes the resource manager session.

    Call viClose(defrm)  'Breaks the communication and terminates the VISA system.

    

    End                                                                             'End

End Sub

 

Sub Cal_Resp(vi As Long, Ch As String, CalType As String, Port As String)

    Dim Dummy As Variant   'Variant to receive the result

    

    Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:METH:" & CalType & " " & Port & vbLf, 0)  'Sets the calibration type.

    

    MsgBox ("Set " & CalType & " to Port " & Port & ". then click [OK] button")  'Display the message box.

    

    Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:" & CalType & " " & Port & vbLf, 0) 'Measurement the calibration data.

    Call viVQueryf(vi, "*OPC?" & vbLf, "%t", Dummy)    'Reads the *OPC? result.

    Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:SAVE" & vbLf, 0)      'Calculating the calibration coefficients.

    

    Call ErrorCheck(vi)      'Checking the error.

    

End Sub

 

Sub Cal_RespThru(vi As Long, Ch As String, CalType As String, Port1 As String, Port2 As String)

    Dim Dummy As Variant   'Variant to receive the result.

    

    If Port1 <> Port2 Then

        Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:METH:" & CalType & " " & Port1 & "," & Port2 & vbLf, 0)   'Sets the calibration type

    

        MsgBox ("Set " & CalType & " to Port " & Port1 & "&" & Port2 & ". then click [OK] button")   'Display the message box.

    

        Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:" & CalType & " " & Port1 & "," & Port2 & vbLf, 0)  'Measurement the calibration data.

        Call viVQueryf(vi, "*OPC?" & vbLf, "%t", Dummy)      'Reads the *OPC? result.

        Call viVPrintf(vi, ":SENS" & Ch & ":CORR:COLL:SAVE" & vbLf, 0)     'Calculating the calibration coefficients.

        

        Call ErrorCheck(vi)     'Checking the error.

    Else

        MsgBox ("Thru calibration select port error!")   'Displaying the error message when selected same ports.

        Exit Sub

    End If

    

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中的样本程序(校准.htb)

10 DIM File$[20],Ch$[9],Inp_char$[9]

20 INTEGER Cal_kit,Cal_type,Port(1:4)

30 !

40 ASSIGN @Agte507x TO 717

50 File$="Ex_4_1.sta"

60 Ch$="1"

70 !

80 Select_cal_kit(@Agte507x,Ch$)

90 !

100 CLEAR SCREEN

110 ON ERROR GOTO Type_select

120 Type_select: !

130 PRINT "## Calibration Type Selection ##"

140 PRINT " 1: Response (Open)"

150 PRINT " 2: Response (Short)"

160 PRINT " 3: Response (Thru)"

170 PRINT " 4: Full 1 Port"

180 PRINT " 5: Full 2 Port"

190 PRINT " 6: Full 3 Port"

200 PRINT " 7: Full 4 Port"

210 PRINT ""

220 PRINT "Input 1 to 7"

230 INPUT "Input number? (1 to 7)",Inp_char$

240 Cal_type=IVAL(Inp_char$,10)

250 IF Cal_type<1 OR Cal_type>7 THEN Type_select

260 OFF ERROR

270 !

280 SELECT Cal_type

290 CASE 1

300 Select_port(1,Port(*))

310 Cal_resp(@Agte507x,Ch$,"OPEN",Port(1))

320 CASE 2

330 Select_port(1,Port(*))

340 Cal_resp(@Agte507x,Ch$,"SHOR",Port(1))

350 CASE 3

360 Select_port(2,Port(*))

370 Cal_resp_thru(@Agte507x,Ch$,Port(1),Port(2))

380 CASE 4

390 Select_port(1,Port(*))

400 Cal_solt(@Agte507x,Ch$,1,Port(*))

410 CASE 5

420 Select_port(2,Port(*))

430 Cal_solt(@Agte507x,Ch$,2,Port(*))

440 CASE 6

450 Select_port(3,Port(*))

460 Cal_solt(@Agte507x,Ch$,3,Port(*))

470 CASE 7

480 Select_port(4,Port(*))

490 Cal_solt(@Agte507x,Ch$,4,Port(*))

500 END SELECT

510 !

520 OUTPUT @Agte507x;":MMEM:STOR:STYP CST"

530 OUTPUT @Agte507x;":MMEM:STOR """&File$&""""

540 END

550 !=============================================

560 ! Calibration Kit Selection Function

570 !=============================================

580 SUB Select_cal_kit(@Agte507x,Ch$)

590 DIM Cal_kit_lbl$(1:10)[20],Inp_char$[9]

600 INTEGER Cal_kit,I

610 CLEAR SCREEN

620 !

630 FOR I=1 TO 10

640 OUTPUT @Agte507x;":SENS1:CORR:COLL:CKIT ";I

650 OUTPUT @Agte507x;":SENS1:CORR:COLL:CKIT:LAB?"

660 ENTER @Agte507x;Cal_kit_lbl$(I)

670 NEXT I

680 ON ERROR GOTO Kit_select

690 Kit_select: !

700 PRINT "## Calibration Kit Selection ##"

710 FOR I=1 TO 10

720 PRINT USING "X,2D,A,X,20A";I,":",Cal_kit_lbl$(I)

730 NEXT I

740 PRINT ""

750 PRINT "Input 1 to 10"

760 INPUT "Input number? (1 to 10)",Inp_char$

770 Cal_kit=IVAL(Inp_char$,10)

780 IF Cal_kit<1 OR Cal_kit>10 THEN Kit_select

790 OFF ERROR

800 !

810 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:CKIT ";Cal_kit

820 SUBEND

830 !=============================================

840 ! Port Selection Function

850 !=============================================

860 SUB Select_port(INTEGER Num_of_ports,INTEGER Port(*))

870 DIM Inp_char$[9]

880 !

890 CLEAR SCREEN

900 IF Num_of_ports=4 THEN

910 Port(1)=1

920 Port(2)=2

930 Port(3)=3

940 Port(4)=4

950 ELSE

960 PRINT "## Test Ports Selection ##"

970 ON ERROR GOTO Port_select

980 FOR I=1 TO Num_of_ports

990 PRINT "Port("&VAL$(I)&"):";

1000 Port_select:!

1010 INPUT "Number?",Inp_char$

1020 Port(I)=IVAL(Inp_char$,10)

1030 IF Port(I)<1 OR Port(I)>4 THEN Port_select

1040 FOR J=1 TO I-1

1050 IF Port(I)=Port(J) THEN Port_select

1060 NEXT J

1070 PRINT Port(I)

1080 NEXT I

1090 OFF ERROR

1100 END IF

1110 SUBEND

1120 !=============================================

1130 ! Response (Open/Short) Calibration Function

1140 !=============================================

1150 SUB Cal_resp(@Agte507x,Ch$,Type$,INTEGER Port)

1160 DIM Buff$[9]

1170 !

1180 PRINT "## Response ("&Type$&") Calibration ##"

1190 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:METH:"&Type$&" ";Port

1200 PRINT "Set "&Type$&" to Port "&VAL$(Port)&". Then push [Enter] key."

1210 INPUT "",Buff$

1220 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:"&Type$&" ";Port

1230 OUTPUT @Agte507x;"*OPC?"

1240 ENTER @Agte507x;Buff$

1250 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:SAVE"

1260 PRINT "Done"

1270 SUBEND

1280 !=============================================

1290 ! Response (Thru) Calibration Function

1300 !=============================================

1310 SUB Cal_resp_thru(@Agte507x,Ch$,INTEGER Port1,Port2)

1320 DIM Buff$[9]

1330 !

1340 PRINT "## Response (Thru) Calibration ##"

1350 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:METH:THRU ";Port1;","; Port2

1360 PRINT "Set THRU between Port "&VAL$(Port1)&" and Port "&VAL$(Port2 )&". Then push [Enter] key."

1370 INPUT "",Buff$

1380 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:THRU ";Port1;",";Port2

1390 OUTPUT @Agte507x;"*OPC?"

1400 ENTER @Agte507x;Buff$

1410 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:SAVE"

1420 PRINT "Done"

1430 SUBEND

1440 !=============================================

1450 ! Full n Port Calibration Function

1460 !=============================================

1470 SUB Cal_solt(@Agte507x,Ch$,INTEGER Num_of_ports,INTEGER Port(*))

1480 DIM Buff$[9]

1490 INTEGER I,J

1500 !

1510 PRINT "## Full "&VAL$(Num_of_ports)&" Port Calibration ##"

1520 !

1530 ! Calibration Type Selection

1540 !

1550 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:METH:SOLT"&VAL$(Num_of_ ports)&" ";

1560 FOR I=1 TO Num_of_ports-1

1570 OUTPUT @Agte507x;Port(I);",";

1580 NEXT I

1590 OUTPUT @Agte507x;Port(Num_of_ports)

1600 !

1610 ! Reflection Measurement

1620 !

1630 FOR I=1 TO Num_of_ports

1640 PRINT "Set OPEN to Port "&VAL$(Port(I))&". Then push [Enter] key."

1650 INPUT "",Buff$

1660 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:OPEN ";Port(I)

1670 OUTPUT @Agte507x;"*OPC?"

1680 ENTER @Agte507x;Buff$

1690 PRINT "Set SHORT to Port "&VAL$(Port(I))&". Then push [Enter] key."

1700 INPUT "",Buff$

1710 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:SHOR ";Port(I)

1720 OUTPUT @Agte507x;"*OPC?"

1730 ENTER @Agte507x;Buff$

1740 PRINT "Set LOAD to Port "&VAL$(Port(I))&". Then push [Enter] key."

1750 INPUT "",Buff$

1760 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:LOAD ";Port(I)

1770 OUTPUT @Agte507x;"*OPC?"

1780 ENTER @Agte507x;Buff$

1790 NEXT I

1800 !

1810 ! Transmission Measurement

1820 !

1830 FOR I=1 TO Num_of_ports-1

1840 FOR J=I+1 TO Num_of_ports

1850 PRINT "Set THRU between Port "&VAL$(Port(I))&" and Port "& VAL$(Port(J))&". Then push [Enter] key."

1860 INPUT "",Buff$

1870 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:THRU ";Port(I);"," ;Port(J)

1880 OUTPUT @Agte507x;"*OPC?"

1890 ENTER @Agte507x;Buff$

1900 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:THRU ";Port(J);"," ;Port(I)

1910 OUTPUT @Agte507x;"*OPC?"

1920 ENTER @Agte507x;Buff$

1930 NEXT J

1940 NEXT I

1950 !

1960 ! Done

1970 !

1980 OUTPUT @Agte507x;":SENS"&Ch$&":CORR:COLL:SAVE"

1990 PRINT "Done"

2000 SUBEND