Attribute VB_Name = "modDPPConfig" Option Explicit '-------------------------------------------------------------------------------------- '@doc clsDPPConfig ' '@module clsDPPConfig Class | DPP (DP4, PX4) Device Configuration Functions ' 'This class has software functionality for DPP (DP4, PX4) Device 'Configuration management. The clsDPPConfig Class is the main repository 'for DPP device configuration data. The clsDPPConfig Class can store and copy 'a DPP device configuration. The current DPP device configuration can 'also be saved to a string for display. ' 'The clsDPPConfig Class does processing of configuration data 'for transmission to a DPP device. The processed configuration buffer can be 'transmitted to the DPP by serial communications port or by USB. ' 'The clsDPPConfig Class also stores and processes status messages and 'live spectral data requested from a DPP device. ' ' Copyright (c)2004 Amptek, All Rights Reserved ' '@devnote ' '@devnote Version: 20040628_0949 ' '@head3 clsDPPConfig Members | '@index | clsDPPConfig ' '-------------------------------------------------------------------------------------- 'add default settings for all clsDPPConfig values ' '------------ 'serial com notes 'Serial commands accepted: '; Sync=FDh, 10 data bytes, End=FEh (config) (11 data bytes for v3.2 or later) '; Sync=FDh, 1 block # byte, End=FFh (send data) '; (data bytes cannot be FDh, FEh or FFh)??? ''------------ Public Const byteSync = &HFD Public Const byteStart = &HFD Public Const byteConfig = &HFE Public Const byteSendData = &HFF Public isCfgChanged As Boolean 'Amptek DPP Device Types Public Const DPPDP4 = &H0 Public Const DPPPX4 = &H1 'indicates type and version of device currently connected to Public DppDevice As Integer 'gen config vars 'Private MCAData(4096) As Long Public MCAData(8192) As Long 'holds the live spectra data Private MCARaw(12288) As Byte 'holds pre-processed spectra data '@bfield Port | Integer | Public Port As Integer 'current com port, -1=none,0=usb,1=com1,2=com2,... '---Process Status Vars------------------------------------------------------------------ '@bfield SlowCount | Long | Public SlowCount As Long 'slow channel count (from status) '@bfield FastCount | Long | Public FastCount As Long 'fast channel count (from status) '@bfield AccumulationTime | Single | Public AccumulationTime As Single 'real time duration of present data acquisition interval '@bfield MCAEnFromStatus | Boolean | Public MCAEnFromStatus As Boolean 'MCA enabled From Status read '---ConfigureDPP Vars-------------------------------------------------------------------- '@bfield Firmware | Byte | Public Firmware As Byte 'firmware revision '@bfield SerialNumber | Long | Public SerialNumber As Long 'unit serial number '@bfield Preset | Long | Public Preset As Long 'var holds preset time, used in usb '---SetDPPConfigBuffer Buffer---------------------------------------------------------------------- '@bfield config(14) | Byte | Private config(14) As Byte 'config data buffer '---SetDPPConfigBuffer Vars----------------------------------------------------------------------- '@bfield Avg | Integer | Public Avg As Integer 'holds decimation setting for pulse shaping '@bfield FlatTop | Integer | Public FlatTop As Integer 'flatop register setting '@bfield DetReset | Byte | Public DetReset As Byte 'detector reset lockout period '@bfield SlowChThreshold | Byte | Public SlowChThreshold As Byte 'Slow ch threshold, Events w/amp lower not added to spectrum '@bfield FastChThreshold | Byte | Public FastChThreshold As Byte 'Fast Ch Threshold, events w/fch amp below this are rejected '@bfield OutputOffset | Long | Public OutputOffset As Long 'Output DAC offset, -64…+63,(signed) (-500mV to +492mV) '@bfield DAC_Enable | Byte | 'Public DAC_Enable As Byte 'dac enabled Public DAC_Off As Boolean 'dac off '@bfield DAC | Integer | Public DAC As Integer 'DAC output type,(stobed peak,shaped pulse,dec inp,fast ch) '@bfield MCA | Integer | Public MCA As Integer 'number of channels 4=256,3=512,2=1024,1=2048,0=4096 '@bfield MCAEnable | Boolean | Public MCAEnable As Boolean 'mca enabled setting '@bfield PUREnable | Boolean | Public PUREnable As Boolean 'pile-up rejection enabled '@bfield Rise | Integer | Public Rise As Integer 'risetime register setting '@bfield BaselineOn | Boolean | Public BaselineOn As Boolean 'use autobaseline during detector reset Public strBaselineOn As String '@bfield RTDSlow | Byte | Public RTDSlow As Byte 'Risetime Discrimination slow threshold '@bfield CoarseGain | Integer | Public CoarseGain As Integer 'analog gain setting (0=10,1=20,2=50,3=100) '@bfield RTDOn | Byte | Public RTDOn As Byte 'Turns RTD on, and sets the amplitude and timing thresholds '@bfield RTDFast | Byte | Public RTDFast As Byte 'RTD Time Threshold,Events w/HWHM wider than this are rejected '@bfield BLR | Byte | Public BLR As Byte 'Baseline Restoration, see udBLR.Value notes for values '@bfield FPGA | Byte | Public FPGA As Byte 'fpga revision '@bfield Gate | Byte | Public Gate As Byte 'gate input settings, determines events included/excluded from spectrum, see DPPGate '@bfield BufferSelect | Byte | Public BufferSelect As Byte 'Holds Buffer Sel A&B,Buffer Sel Hardware,see DPPBufferSelect Public FineGain As Integer Public InvertCG As Boolean 'invert coarse gain ' Power Properties Public TEC_On As Boolean Public Pwr5VA_On As Boolean Public XR100_On As Boolean Public Pwr9V_On As Boolean Public Pwr8_5SEL_On As Boolean Public LED_On As Boolean Public Buzzer_On As Boolean Public InputOffset As Long ' input offset Public TEC As Integer ' TEC temperature setting (displayed in Kelvin) 'Public HVEnabled As Byte ' high voltage setting enable Public HV As Integer ' high voltage setting value Public PreampPower As Byte ' preamp power select value (5v or 8.5v) ' Misc Properties Public AnalogOut As Byte ' dac enabled and DAC output type,(stobed peak,shaped pulse,dec inp,fast ch) 'Public OutputOffset As Byte ' Output DAC offset, -64…+63,(signed)(D7-D1) (-500mV to +492mV) Public AuxOut As Byte ' Aux output type Public AudibleCounter As Byte ' audio volume setting Public PoleZero As Integer ' pole zero adjust value Public AcqMode As Byte ' acquisition mode 0=MCA,1=MCS Public MCSTimebase As Byte ' MCS timebase value (0-15) see CAcqMode Public MCAChannels As Byte ' number of channels 4=256,3=512,2=1024,1=2048,0=4096,5=8192 Public MCSEnable As Byte ' MCS Enable (Always ON, Gate Signal-if low prevents counts to current mcs channel) 'values for MCA Public Const MCA256 = 4 Public Const MCA512 = 3 Public Const MCA1024 = 2 Public Const MCA2048 = 1 Public Const MCA4096 = 0 Public Const MCA8192 = 5 Public Const BufferSelectA = 0 '@emem bufselA = 0 | select buffer A Public Const BufferSelectB = 16 '@emem bufselB = 16 | select buffer B Public Const BufferSelectHW = 32 '@emem bufselHW = 32 | buffer selected by Hardware Public Const GateOff = 0 Public Const GateHigh = 128 Public Const GateLow = 192 ' Variables and constants need by both Form1 & Form_SCA Public SCA(8, 2) As Long Public SCA_Enable(8) As Integer Public Preset_counts As Long 'Public Const ConfigNeededColor As Long = vbYellow Public Handle_device As Long 'vbYellow = &HFFFF& Public Const ConfigNeededColor = &HFFFF& 'config data changed, set config btn yel Private Function GetRiseTextValue(RiseIndex As Long) As String Dim idxRiseText As Long Dim idxAve As Long Dim idxX As Long Dim RiseTextArray(23) As String Dim strMsg As String strMsg = "" If ((RiseIndex < 0) Or (RiseIndex > 23)) Then Exit Function idxRiseText = -1 For idxX = 1 To 8 idxRiseText = idxRiseText + 1 RiseTextArray(idxRiseText) = CStr(idxX * 0.8) + "uS" strMsg = strMsg & RiseTextArray(idxRiseText) & vbNewLine Next idxX 'MsgBox strMsg For idxAve = 1 To 4 strMsg = "" For idxX = 5 To 8 idxRiseText = idxRiseText + 1 RiseTextArray(idxRiseText) = CStr(idxX * 0.8 * (2 ^ idxAve)) + "uS" strMsg = strMsg & RiseTextArray(idxRiseText) & vbNewLine Next idxX 'MsgBox strMsg Next idxAve 'MsgBox RiseTextArray(RiseIndex) GetRiseTextValue = RiseTextArray(RiseIndex) End Function Public Function CheckRangeCsng(TestVal As Single, MinVal As Single, MaxVal As Single) CheckRangeCsng = CBool((TestVal >= MinVal) And (TestVal <= MaxVal)) End Function 'Sets Rise and Avg global values from stored combobox index '!!!! FlatTop = FlatTop combobox control index value Public Sub SetRiseAndAvg(RiseIndex As Long) Dim strRiseText As String Dim SngRiseVal As Single If ((RiseIndex < 0) Or (RiseIndex > 23)) Then Exit Sub strRiseText = GetRiseTextValue(RiseIndex) 'MsgBox "strRiseText " & strRiseText SngRiseVal = CSng(Val(strRiseText)) 'MsgBox "SngRiseVal " & SngRiseVal If CheckRangeCsng(SngRiseVal, 0, 6.4) Then Rise = SngRiseVal / 0.8 Avg = 1 ElseIf CheckRangeCsng(SngRiseVal, 8, 12.8) Then Rise = SngRiseVal / 1.6 Avg = 2 ElseIf CheckRangeCsng(SngRiseVal, 16, 25.6) Then Rise = SngRiseVal / 3.2 Avg = 3 ElseIf CheckRangeCsng(SngRiseVal, 32, 51.2) Then Rise = SngRiseVal / 6.4 Avg = 4 ElseIf CheckRangeCsng(SngRiseVal, 64, 102.4) Then Rise = SngRiseVal / 12.8 Avg = 5 End If End Sub 'Sets Rise and Avg global values from stored combobox index '!!!! FlatTop = FlatTop combobox control index value Public Sub SetRiseAndAvgFromString(strRiseText As String) Dim SngRiseVal As Single 'MsgBox "strRiseText " & strRiseText SngRiseVal = CSng(Val(strRiseText)) 'MsgBox "SngRiseVal " & SngRiseVal If CheckRangeCsng(SngRiseVal, 0, 6.4) Then Rise = SngRiseVal / 0.8 Avg = 1 ElseIf CheckRangeCsng(SngRiseVal, 8, 12.8) Then Rise = SngRiseVal / 1.6 Avg = 2 ElseIf CheckRangeCsng(SngRiseVal, 16, 25.6) Then Rise = SngRiseVal / 3.2 Avg = 3 ElseIf CheckRangeCsng(SngRiseVal, 32, 51.2) Then Rise = SngRiseVal / 6.4 Avg = 4 ElseIf CheckRangeCsng(SngRiseVal, 64, 102.4) Then Rise = SngRiseVal / 12.8 Avg = 5 End If End Sub Private Function GetFlatTopTextValue(FlatTopIndex As Long) As String Dim idxFlatTopText As Long Dim idxX As Long Dim FlatTopTextArray(15) As String If ((FlatTopIndex < 0) Or (FlatTopIndex > 15)) Then Exit Function idxFlatTopText = -1 For idxX = 1 To 16 idxFlatTopText = idxFlatTopText + 1 FlatTopTextArray(idxFlatTopText) = CStr(idxX * 0.1 * (2 ^ Avg)) + "uS" Next idxX GetFlatTopTextValue = FlatTopTextArray(FlatTopIndex) End Function Public Sub SetFlatTopFromIndex(FlatTopIndex As Long) Dim strFlatTopText As String If ((FlatTopIndex < 0) Or (FlatTopIndex > 15)) Then Exit Sub strFlatTopText = GetFlatTopTextValue(FlatTopIndex) FlatTop = (Val(strFlatTopText) / 0.1 / (2 ^ Avg) - 1) End Sub 'Public Function GetRiseStringFromVal(RiseVal As Integer, AvgVal As Integer) As String ' If (AvgVal = 0) Then ' GetRiseStringFromVal = "" '"Rise Value Not Set" ' ElseIf (RiseVal = -1) Then ' GetRiseStringFromVal = "" '"Rise Value Not Set" ' Else ' GetRiseStringFromVal = CStr(RiseVal * 0.8 * (2 ^ (AvgVal - 1))) & "uS" ' End If 'End Function ' 'Public Function GetTopStringFromVal(FlatTopVal As Integer, AvgVal As Integer) As String ' Dim dblTop As Double ' dblTop = 0.1 * (2 ^ AvgVal) * (FlatTopVal + 1) ' GetTopStringFromVal = CStr(dblTop) & "uS" 'End Function Public Function GetRiseIndex(RiseVal As Integer, AvgVal As Integer) As Integer Dim lowVal As Integer Dim grpIdx As Integer lowVal = RiseVal \ 5 'checks if rise < 5 grpIdx = RiseVal Mod 5 'get pos in group GetRiseIndex = (grpIdx + (lowVal * (4 * AvgVal + 1)) - 1) End Function Public Sub SetPresetTimeFromStr(strPresetTime As String) Select Case strPresetTime Case "None" Preset = 0 Case "1 sec" Preset = 10 Case "2 sec" Preset = 20 Case "5 sec" Preset = 50 Case "10 sec" Preset = 100 Case "30 sec" Preset = 300 Case "1 min" Preset = 600 Case "2 min" Preset = 1200 Case "5 min" Preset = 3000 Case "10 min" Preset = 6000 Case "30 min" Preset = 18000 Case "1 hr" Preset = 36000 Case "2 hr" Preset = 72000 Case "5 hr" Preset = 180000 Case "10 hr" Preset = 360000 Case "24 hr" Preset = 864000 Case Else Preset = CLng(Val(strPresetTime) * 10) End Select End Sub 'Public Function GetPresetTimeStrFromVal(PresetVal As Long) As String ' Select Case PresetVal ' Case 0 ' GetPresetTimeStrFromVal = "None" ' Case 10 ' GetPresetTimeStrFromVal = "1 sec" ' Case 20 ' GetPresetTimeStrFromVal = "2 sec" ' Case 50 ' GetPresetTimeStrFromVal = "5 sec" ' Case 100 ' GetPresetTimeStrFromVal = "10 sec" ' Case 300 ' GetPresetTimeStrFromVal = "30 sec" ' Case 600 ' GetPresetTimeStrFromVal = "1 min" ' Case 1200 ' GetPresetTimeStrFromVal = "2 min" ' Case 3000 ' GetPresetTimeStrFromVal = "5 min" ' Case 6000 ' GetPresetTimeStrFromVal = "10 min" ' Case 18000 ' GetPresetTimeStrFromVal = "30 min" ' Case 36000 ' GetPresetTimeStrFromVal = "1 hr" ' Case 72000 ' GetPresetTimeStrFromVal = "2 hr" ' Case 180000 ' GetPresetTimeStrFromVal = "5 hr" ' Case 360000 ' GetPresetTimeStrFromVal = "10 hr" ' Case 864000 ' GetPresetTimeStrFromVal = "24 hr" ' Case Else ' GetPresetTimeStrFromVal = CLng(Val(PresetVal) / 10) & " sec" ' End Select 'End Function 'create separate function to process data from controls and graphics 'create process data controls function '------spectra data read/write functions------ '@bsub gets entire live spectra data buffer '@bparm | lngMCAData( ) | Long | live spectra data destination buffer Public Sub GetMCAData(lngMCAData() As Long) Dim I As Integer For I = LBound(MCAData) To UBound(MCAData) lngMCAData(I) = MCAData(I) Next End Sub '@bsub sets entire live spectra data buffer '@bparm | lngMCAData( ) | Long | live spectra data source buffer Public Sub SetMCAData(lngMCAData() As Long) Dim I As Integer For I = LBound(lngMCAData) To UBound(lngMCAData) MCAData(I) = lngMCAData(I) Next End Sub '@bfunc gets a live spectra data buffer value '@bparm live spectra data buffer index to be read '@rdesc live spectra data buffer value Public Function GetMCADataVal(lngIndex As Long) As Long GetMCADataVal = MCAData(lngIndex) End Function '@bsub Sets a live spectra data buffer value '@bparm live spectra data value '@bparm live spectra data buffer index to be changed Public Sub SetMCADataVal(lngMCAData As Long, lngIndex As Long) MCAData(lngIndex) = lngMCAData End Sub '================================================================= '------raw data read/write functions------ '@bsub gets entire raw spectra data buffer '@bparm | lngMCAData( ) | Byte | raw spectra data destination buffer Public Sub GetMCARaw(lngMCAData() As Byte) Dim I As Integer For I = LBound(MCARaw) To UBound(MCARaw) lngMCAData(I) = MCARaw(I) Next End Sub '@bsub sets entire raw spectra data buffer '@bparm | lngMCAData( ) | Byte | raw spectra data source buffer Public Sub SetMCARaw(lngMCAData() As Byte) Dim I As Integer For I = LBound(lngMCAData) To UBound(lngMCAData) MCARaw(I) = lngMCAData(I) Next End Sub '@bfunc gets a raw spectra data buffer value '@bparm raw spectra data buffer index to be read '@rdesc raw spectra data buffer value Public Function GetMCARawVal(lngIndex As Long) As Long GetMCARawVal = MCARaw(lngIndex) End Function '@bsub Sets a raw spectra data buffer value '@bparm raw spectra data value '@bparm raw spectra data buffer index to be changed Public Sub SetMCARawVal(lngMCAData As Byte, lngIndex As Long) MCARaw(lngIndex) = lngMCAData End Sub '================================================================= 'only clears values used to set dpp config '!!!!!! in future set to defaults, also add set flag '@bsub clears all the configuration values to 0 '@devnote in future set, will have similar function to set config to defaults Public Sub ClearConfig() '---SetDPPConfigBuffer Vars----------------------------------------------------------------------- Avg = 1 'holds decimation setting for pulse shaping FlatTop = 0 'flatop register setting DetReset = 2 'detector reset lockout period SlowChThreshold = 4 'Slow ch threshold, Events w/amp lower not added to spectrum FastChThreshold = 100 'Fast Ch Threshold, events w/fch amp below this are rejected OutputOffset = 13 'Output DAC offset, -64…+63,(signed) (-500mV to +492mV) 'DAC_Enable = 1 'dac enabled DAC_Off = False DAC = 1 'DAC output type,(stobed peak,shaped pulse,dec inp,fast ch) MCA = 2 'number of channels 4=256,3=512,2=1024,1=2048,0=4096 MCAEnable = True 'mca enabled setting PUREnable = True 'pile-up rejection enabled Rise = 1 'risetime register setting BaselineOn = True 'use autobaseline during detector reset RTDSlow = 0 'Risetime Discrimination slow threshold CoarseGain = 0 'analog gain setting (0=10,1=20,2=50,3=100) RTDOn = 0 'Turns RTD on, and sets the amplitude and timing thresholds RTDFast = 10 'RTD Time Threshold,Events w/HWHM wider than this are rejected BLR = 63 'Baseline Restoration, see udBLR.Value notes for values FPGA = 0 'fpga revision Gate = 0 'gate input settings, determines events included/excluded from spectrum, see DPPGate BufferSelect = 0 'Holds Buffer Sel A&B,Buffer Sel Hardware,see DPPBufferSelect Preset = 0 'var holds preset time, used in usb 'Port = -1 End Sub '@bsub converts the configuration values to a display string '@comm each configuration value is displayed on a separate line Public Function ShowConfigVals() As String Dim strVal As String strVal = "" '---SetDPPConfigBuffer Vars----------------------------------------------------------------------- strVal = strVal & "Avg = " & Avg & vbNewLine 'holds decimation setting for pulse shaping" strVal = strVal & "FlatTop = " & FlatTop & vbNewLine 'flatop register setting" strVal = strVal & "DetReset = " & DetReset & vbNewLine 'detector reset lockout period" strVal = strVal & "SlowChThreshold = " & SlowChThreshold & vbNewLine 'Slow ch threshold, Events w/amp lower not added to spectrum" strVal = strVal & "FastChThreshold = " & FastChThreshold & vbNewLine 'Fast Ch Threshold, events w/fch amp below this are rejected" strVal = strVal & "OutputOffset = " & OutputOffset & vbNewLine 'Output DAC offset, -64…+63,(signed) (-500mV to +492mV)" 'strVal = strVal & "DAC_Enable = " & DAC_Enable & vbNewLine 'dac enabled" strVal = strVal & "DAC_Enable = " & DAC_Off & vbNewLine 'dac enabled" strVal = strVal & "DAC = " & DAC & vbNewLine 'DAC output type,(stobed peak,shaped pulse,dec inp,fast ch)" strVal = strVal & "MCA = " & MCA & vbNewLine 'number of channels 4=256,3=512,2=1024,1=2048,0=4096" strVal = strVal & "MCAEnable = " & MCAEnable & vbNewLine 'mca enabled setting" strVal = strVal & "PUREnable = " & PUREnable & vbNewLine 'pile-up rejection enabled" strVal = strVal & "Rise = " & Rise & vbNewLine 'risetime register setting" strVal = strVal & "BaselineOn = " & BaselineOn & vbNewLine 'use autobaseline during detector reset" strVal = strVal & "RTDSlow = " & RTDSlow & vbNewLine 'Risetime Discrimination slow threshold" strVal = strVal & "CoarseGain = " & CoarseGain & vbNewLine 'analog gain setting (0=10,1=20,2=50,3=100)" strVal = strVal & "RTDOn = " & RTDOn & vbNewLine 'Turns RTD on, and sets the amplitude and timing thresholds" strVal = strVal & "RTDFast = " & RTDFast & vbNewLine 'RTD Time Threshold,Events w/HWHM wider than this are rejected" strVal = strVal & "BLR = " & BLR & vbNewLine 'Baseline Restoration, see udBLR.Value notes for values" strVal = strVal & "FPGA = " & FPGA & vbNewLine 'fpga revision" strVal = strVal & "Gate = " & Gate & vbNewLine 'gate input settings, determines events included/excluded from spectrum, see DPPGate" strVal = strVal & "BufferSelect = " & BufferSelect & vbNewLine 'Holds Buffer Sel A&B,Buffer Sel Hardware,see DPPBufferSelect" strVal = strVal & "Preset = " & Preset & vbNewLine 'var holds preset time, used in usb ShowConfigVals = strVal End Function Public Sub DoConfigChanged() isCfgChanged = True End Sub Public Sub DoDialogChanged() isCfgChanged = False End Sub Private Sub Class_Initialize() isCfgChanged = False End Sub 'Public Function ShowBytes(MCATemp As Variant) As String ' 'MCATemp() As Byte ' Dim i As Integer ' Dim strMsg As String ' strMsg = "" ' For i = LBound(MCATemp) To UBound(MCATemp) ' strMsg = strMsg & Hex(MCATemp(i)) & vbNewLine ' Next ' ShowBytes = strMsg 'End Function ' 'Public Sub SaveBufferToFile(strDescription As String, Buffer As Variant, UseDTS As Boolean) ' 'Buffer() As Byte ' Dim FileNumber As Integer ' Dim strDTS As String ' FileNumber = FreeFile ' strDTS = "" ' If UseDTS Then strDTS = Format(Now, "_YYYYMMDD_HHNNSS") ' Open App.Path & "\" & strDescription & strDTS & ".hm" For Output As #FileNumber ' Print #FileNumber, ShowBytes(Buffer) ' Close #FileNumber 'End Sub Private Function SaveConfigToString() As String Dim strCfg As String strCfg = "" strCfg = strCfg & GetRiseIndex(Rise, Avg) & vbNewLine strCfg = strCfg & FlatTop & vbNewLine strCfg = strCfg & SlowChThreshold & vbNewLine strCfg = strCfg & FastChThreshold & vbNewLine strCfg = strCfg & OutputOffset & vbNewLine If (PUREnable) Then strCfg = strCfg & "PUROn" & vbNewLine Else strCfg = strCfg & "PUROff" & vbNewLine End If strCfg = strCfg & DetReset & vbNewLine If DAC_Off Then strCfg = strCfg & "DAC5" & vbNewLine ElseIf (DAC = 0) Then strCfg = strCfg & "DAC1" & vbNewLine ElseIf (DAC = 1) Then strCfg = strCfg & "DAC2" & vbNewLine ElseIf (DAC = 2) Then strCfg = strCfg & "DAC3" & vbNewLine ElseIf (DAC = 3) Then strCfg = strCfg & "DAC4" & vbNewLine Else strCfg = strCfg & "DAC5" & vbNewLine End If If (MCA = 4) Then strCfg = strCfg & "MCA256" & vbNewLine ElseIf (MCA = 3) Then strCfg = strCfg & "MCA512" & vbNewLine ElseIf (MCA = 2) Then strCfg = strCfg & "MCA1024" & vbNewLine ElseIf (MCA = 1) Then strCfg = strCfg & "MCA2048" & vbNewLine ElseIf (MCA = 0) Then strCfg = strCfg & "MCA4096" & vbNewLine ElseIf (MCA = 5) Then strCfg = strCfg & "MCADisable" & vbNewLine Else strCfg = strCfg & "MCA not selected" & vbNewLine End If If ((Port > 0) And (Port < 10)) Then strCfg = strCfg & "COM" & CStr(Port) & vbNewLine Else strCfg = strCfg & "COM1" & vbNewLine End If If (RTDOn) Then strCfg = strCfg & "RTDOn" & vbNewLine Else strCfg = strCfg & "RTDOff" & vbNewLine End If strCfg = strCfg & RTDSlow & vbNewLine strCfg = strCfg & RTDFast & vbNewLine strCfg = strCfg & CoarseGain & vbNewLine ' modified in v3.6 for PX4/DP4 gain ' the following were added in v3.4 If BaselineOn Then strCfg = strCfg & "AutoBaselineOn" & vbNewLine Else strCfg = strCfg & "AutoBaselineOff" & vbNewLine End If strCfg = strCfg & BLR & vbNewLine If (BufferSelect = BufferSelectA) Then strCfg = strCfg & "BufferSelectA" & vbNewLine ElseIf (BufferSelect = BufferSelectB) Then strCfg = strCfg & "BufferSelectB" & vbNewLine ElseIf (BufferSelect = BufferSelectHW) Then strCfg = strCfg & "BufferSelectHW" & vbNewLine Else strCfg = strCfg & "BufferSelectA" & vbNewLine End If If (Gate = GateOff) Then strCfg = strCfg & "GateOff" & vbNewLine ElseIf (Gate = GateHigh) Then strCfg = strCfg & "GateHigh" & vbNewLine ElseIf (Gate = GateLow) Then strCfg = strCfg & "GateLow" & vbNewLine Else strCfg = strCfg & "GateOff" & vbNewLine End If strCfg = strCfg & GetPresetTimeStrFromVal(Preset) & vbNewLine ' The following were added in v3.6 strCfg = strCfg & FineGain & vbNewLine strCfg = strCfg & Abs(TEC_On) & vbNewLine strCfg = strCfg & 0 & vbNewLine ' used to be chk5VA.Value strCfg = strCfg & Abs(Pwr8_5SEL_On) & vbNewLine strCfg = strCfg & 0 & vbNewLine ' used to be chkXR100.Value strCfg = strCfg & Abs(Pwr9V_On) & vbNewLine strCfg = strCfg & Abs(InvertCG) & vbNewLine strCfg = strCfg & InputOffset & vbNewLine strCfg = strCfg & PoleZero & vbNewLine strCfg = strCfg & AuxOut & vbNewLine ' The following were added in v3.8 strCfg = strCfg & HV & vbNewLine strCfg = strCfg & TEC & vbNewLine SaveConfig = strCfg End Function