News:

:) Welcome to the Probe Software forum area!

Main Menu

History of EPMA

Started by John Donovan, May 04, 2017, 12:37:25 PM

Previous topic - Next topic

sem-geologist

I would look to this issue from different perspective. Why not to drop jet completely? PfS is using SQL to interact with jet? why not make platform/db agnostic SQL IO and make it possible to use any free SQL databases, be it on files (i.e. SQLite) or real distributed databases (postgreSQL, mariadb, MySQL, MSSQL, Oracle....)?

John Donovan

Quote from: sem-geologist on March 27, 2025, 03:07:29 AMI would look to this issue from different perspective. Why not to drop jet completely? PfS is using SQL to interact with jet? why not make platform/db agnostic SQL IO and make it possible to use any free SQL databases, be it on files (i.e. SQLite) or real distributed databases (postgreSQL, mariadb, MySQL, MSSQL, Oracle....)?

By PfS do you mean Probe for EPMA? 

PFE uses a mixture of Jet and SQL calls. I am not an expert on the Jet database access and only use it as a data storage method. It's nice because the MDB file automatically handles the file format and also includes transaction processing methods. This is used because if an error occurs during a database write opertion (e.g., computer crashes), the database automatically rolls back to the previous state. Similar to how money is transferred from one account to another!

Remember, these database calls were first written in the early 1990s!  The fact that we can read these databases in Windows 11 is amazing to me as I described in my post above on backwards compatibility:

https://smf.probesoftware.com/index.php?topic=924.msg13203#msg13203

If anyone is interested in looking at the MDB database code and see what is utilized, see the open source code for CalcZAF/Standard on GitHub:

https://github.com/openmicroanalysis/calczaf

For example, the Standard compositional database code is in general pretty similar to the database code used in Probe for EPMA.  And of course we are happy to share database code examples in Probe for EPMA for anyone to examine.

Here is an code example for reading a sample in Probe for EPMA:

Sub DataGetMDBSample(samplerow As Integer, sample() As TypeSample)
' This routine reads the user data file (*.MDB) to obtain the sample data for the indicated sample row

ierror = False
On Error GoTo DataGetMDBSampleError

Dim n As Integer, m As Integer
Dim chan As Integer, row As Integer
Dim temp As Single, fuzz As Single
Dim SQLQ As String

Dim PrDb As Database
Dim PrRs As Recordset

' Update status
'Call IOStatusAuto("Loading sample " & SampleGetString$(samplerow%) & "...")
'Call AnalyzeStatusAnal("Loading sample " & SampleGetString$(samplerow%) & "...")
'DoEvents

' Load sample parameters only (no intensity data)
Call DataGetMDBSampleOnly(samplerow%, sample())
If ierror Then Exit Sub

' Allocate count and background arrays
ReDim sample(1).CorData(1 To MAXROW%, 1 To MAXCHAN1%) As Single
ReDim sample(1).BgdData(1 To MAXROW%, 1 To MAXCHAN1%) As Single
ReDim sample(1).ErrData(1 To MAXROW%, 1 To MAXCHAN1%) As Single
   
ReDim sample(1).OnTimeData(1 To MAXROW%, 1 To MAXCHAN1%) As Single      ' for aggregate intensity calculations
ReDim sample(1).HiTimeData(1 To MAXROW%, 1 To MAXCHAN1%) As Single      ' for aggregate intensity calculations
ReDim sample(1).LoTimeData(1 To MAXROW%, 1 To MAXCHAN1%) As Single      ' for aggregate intensity calculations

ReDim sample(1).OnBeamData(1 To MAXROW%, 1 To MAXCHAN1%) As Single      ' for aggregate intensity calculations (average aggregate beam)
ReDim sample(1).OnBeamDataArray(1 To MAXROW%, 1 To MAXCHAN1%) As Single      ' for aggregate intensity calculations (average aggregate beam)

ReDim sample(1).AggregateNumChannels(1 To MAXROW%, 1 To MAXCHAN1%) As Integer      ' for aggregate intensity calculations (number of aggregate channels)

' Open the database using error trapping for databases already open for exclusive use by another app
Screen.MousePointer = vbHourglass
Call DataOpenDatabase("DataGetMDBSample", PrDb, ProbeDataFile$, ProbeDatabaseNonExclusiveAccess%, dbReadOnly)
If ierror Then Exit Sub

' Get Count data for specified sample from probe database (raw cps with no beam current correction)
SQLQ$ = "SELECT Count.* FROM Count WHERE Count.CountToRow = " & Str$(samplerow%)
Set PrRs = PrDb.OpenRecordset(SQLQ$, dbOpenSnapshot)

' Use "ElementOrder" and "LineOrder" fields to load element and lines in order (if no data, just drops through)
Do Until PrRs.EOF
chan% = PrRs("ElementOrder")
row% = PrRs("LineOrder")
If chan% < 1 Or chan% > MAXCHAN% Then GoTo DataGetMDBSampleBadChannel
If row% < 1 Or row% > MAXROW% Then GoTo DataGetMDBSampleBadRow

sample(1).OnPeakCounts!(row%, chan%) = PrRs("OnCount")                                                 ' on peak intensites
sample(1).OnPeakCounts_Raw_Cps!(row%, chan%) = sample(1).OnPeakCounts!(row%, chan%)                    ' save for statistics calculations!!!!!!!

sample(1).HiPeakCounts!(row%, chan%) = PrRs("HiCount")                                                 ' high off peak intensities for stds/unks or spectrometer position for wavescans
sample(1).HiPeakCounts_Raw_Cps!(row%, chan%) = sample(1).HiPeakCounts!(row%, chan%)                    ' save for statistics calculations!!!!!!!

sample(1).LoPeakCounts!(row%, chan%) = PrRs("LoCount")                                                 ' low off peak intensities for stds/unkns or angstrom values for wavescans
sample(1).LoPeakCounts_Raw_Cps!(row%, chan%) = sample(1).LoPeakCounts!(row%, chan%)                    ' save for statistics calculations!!!!!!!

sample(1).OnCountTimes!(row%, chan%) = PrRs("OnCountTime")
sample(1).HiCountTimes!(row%, chan%) = PrRs("HiCountTime")
sample(1).LoCountTimes!(row%, chan%) = PrRs("LoCountTime")

' Get unknown count factors
If ProbeDataFileVersionNumber! > 2.44 Then
sample(1).UnknownCountFactors!(row%, chan%) = PrRs("UnknownCountFactor")
End If

' Get unknown max counts
If ProbeDataFileVersionNumber! > 4# Then
sample(1).UnknownMaxCounts&(row%, chan%) = PrRs("UnknownMaxCount")
End If

' Add beam count arrays (combined samples only)
If ProbeDataFileVersionNumber! > 5.01 Then
sample(1).OnBeamCountsArray!(row%, chan%) = PrRs("OnBeamCountsArray")   ' use for faraday beam
End If

' If no beam current then use default beam current (for old wavescan samples)
If ProbeDataFileVersionNumber! <= 8.28 And sample(1).Type% = 3 Then
If sample(1).OnBeamCountsArray!(row%, chan%) = 0# Then sample(1).OnBeamCountsArray!(row%, chan%) = DefaultBeamCurrent!
End If

' Get volatile element acquisition times
If ProbeDataFileVersionNumber! > 6.46 Then
sample(1).VolCountTimesStart(row%, chan%) = PrRs("VolCountTimesStart")
sample(1).VolCountTimesStop(row%, chan%) = PrRs("VolCountTimesStop")
If IsNull(sample(1).VolCountTimesStart(row%, chan%)) Then sample(1).VolCountTimesStart(row%, chan%) = 0#
If IsNull(sample(1).VolCountTimesStop(row%, chan%)) Then sample(1).VolCountTimesStop(row%, chan%) = 0#
End If

' Get volatile element faraday delay time
If ProbeDataFileVersionNumber! > 8.26 Then
sample(1).VolCountTimesDelay!(row%, chan%) = PrRs("VolCountTimesDelay")
End If

' Add beam count arrays (combined samples only)
If ProbeDataFileVersionNumber! > 10.65 Then
sample(1).AbBeamCountsArray!(row%, chan%) = PrRs("AbBeamCountsArray")   ' use for absorbed beam
End If

' Add beam count arrays (combined samples only)
If ProbeDataFileVersionNumber! > 10.68 Then
sample(1).OnBeamCountsArray2!(row%, chan%) = PrRs("OnBeamCountsArray2")   ' use for second faraday beam
sample(1).AbBeamCountsArray2!(row%, chan%) = PrRs("AbBeamCountsArray2")   ' use for second absorbed beam
End If

PrRs.MoveNext
Loop

PrRs.Close

' Get integrated intensities
If ProbeDataFileVersionNumber! > 5.22 Then
SQLQ$ = "SELECT Inte.* FROM Inte WHERE Inte.InteToRow = " & Str$(samplerow%)
Set PrRs = PrDb.OpenRecordset(SQLQ$, dbOpenSnapshot)

' Zero arrays
If sample(1).Datarows% > 0 And sample(1).LastElm% > 0 Then
ReDim sample(1).IntegratedPoints(1 To sample(1).Datarows%, 1 To sample(1).LastElm%) As Integer
ReDim sample(1).IntegratedPeakIntensities(1 To sample(1).Datarows%, 1 To sample(1).LastElm%) As Single   ' loaded in DataCorrectData
ReDim sample(1).IntegratedPositions(1 To sample(1).Datarows%, 1 To sample(1).LastElm%, 1 To 1) As Single
ReDim sample(1).IntegratedIntensities(1 To sample(1).Datarows%, 1 To sample(1).LastElm%, 1 To 1) As Single
ReDim sample(1).IntegratedCountTimes(1 To sample(1).Datarows%, 1 To sample(1).LastElm%, 1 To 1) As Single

' Use "InteElementOrder" and "InteLineOrder" fields to load element and lines in order
m% = 0
Do Until PrRs.EOF
chan% = PrRs("InteElementOrder")
row% = PrRs("InteLineOrder")
n% = PrRs("InteInteOrder")
If chan% < 1 Or chan% > sample(1).LastElm% Then GoTo DataGetMDBSampleBadIntegratedChannel
If row% < 1 Then GoTo DataGetMDBSampleBadIntegratedRow
If row% > sample(1).Datarows% Then GoTo DataGetMDBSampleBadIntegratedRowSkip        ' sample is being acquired!
If n% < 1 Then GoTo DataGetMDBSampleBadIntegratedIncrement

' Check for invalid integrated sample (do not exit)
If sample(1).IntegratedIntensitiesUseIntegratedFlags%(chan%) <> True Then
Screen.MousePointer = vbDefault
msg$ = "Warning: " & SampleGetString$(samplerow%) & " channel " & Format$(chan%) & " is not flagged as an integrated intensity channel in " & ProbeDataFile$
MsgBox msg$, vbOKOnly + vbInformation, "DataGetMDBSample"
'ierror = True
Exit Do
End If

' Check array dimensions and increase if necessary
If n% > m% Then
ReDim Preserve sample(1).IntegratedPositions(1 To sample(1).Datarows%, 1 To sample(1).LastElm%, 1 To n%) As Single
ReDim Preserve sample(1).IntegratedIntensities(1 To sample(1).Datarows%, 1 To sample(1).LastElm%, 1 To n%) As Single
ReDim Preserve sample(1).IntegratedCountTimes(1 To sample(1).Datarows%, 1 To sample(1).LastElm%, 1 To n%) As Single
m% = n%
End If

' Check if x-axis data is identical to previous position (6 * Rnd) + 1
If n% > 1 Then
If sample(1).IntegratedPositions!(row%, chan%, n% - 1) = PrRs("IntePositions") Then
fuzz! = Rnd() * 0.5
sample(1).IntegratedPositions!(row%, chan%, n% - 1) = sample(1).IntegratedPositions!(row%, chan%, n% - 1) - fuzz!
End If
End If

' Store largest value for this row and channel
If n% > sample(1).IntegratedPoints%(row%, chan%) Then
sample(1).IntegratedPoints%(row%, chan%) = n%
End If

sample(1).IntegratedPositions!(row%, chan%, n%) = PrRs("IntePositions")
sample(1).IntegratedIntensities!(row%, chan%, n%) = PrRs("InteIntensities")
sample(1).IntegratedCountTimes!(row%, chan%, n%) = PrRs("InteCountTimes")

' Stored integrated intensities are raw counts
If sample(1).IntegratedCountTimes!(row%, chan%, n%) <> 0# Then
sample(1).IntegratedIntensities!(row%, chan%, n%) = sample(1).IntegratedIntensities!(row%, chan%, n%) / sample(1).IntegratedCountTimes!(row%, chan%, n%)
End If

DataGetMDBSampleBadIntegratedRowSkip:
PrRs.MoveNext
Loop

End If
PrRs.Close
End If

' Get multi-point intensities
If ProbeDataFileVersionNumber! > 8.31 Then
SQLQ$ = "SELECT MultiPoint.* FROM MultiPoint WHERE MultiPoint.MultiPointToRow = " & Str$(samplerow%)
Set PrRs = PrDb.OpenRecordset(SQLQ$, dbOpenSnapshot)

' Use "ElementOrder" and "LineOrder" fields to load element and lines in order
Do Until PrRs.EOF
chan% = PrRs("ElementOrder")
row% = PrRs("LineOrder")
m% = PrRs("MultiPointOrder")
If chan% < 1 Or chan% > MAXCHAN% Then GoTo DataGetMDBSampleBadChannel
If row% < 1 Or row% > MAXROW% Then GoTo DataGetMDBSampleBadRow
If m% < 1 Or m% > MAXMULTI% Then GoTo DataGetMDBSampleBadMultiPoint

If m% <= MAXMULTI_OLD% Or ProbeDataFileVersionNumber! >= 12.84 Then
sample(1).MultiPointAcquireCountTimesHi!(row%, chan%, m%) = PrRs("HiCountTimes")
sample(1).MultiPointAcquireCountTimesLo!(row%, chan%, m%) = PrRs("LoCountTimes")
sample(1).MultiPointAcquireCountsHi!(row%, chan%, m%) = PrRs("HiCounts")
sample(1).MultiPointAcquireCountsLo!(row%, chan%, m%) = PrRs("LoCounts")
sample(1).MultiPointProcessManualFlagHi%(row%, chan%, m%) = PrRs("HiManualFlag")
sample(1).MultiPointProcessManualFlagLo%(row%, chan%, m%) = PrRs("LoManualFlag")
End If

PrRs.MoveNext
Loop

PrRs.Close
End If

' Close the probe database
Screen.MousePointer = vbDefault
PrDb.Close

' Make sure objects are deallocated
If Not PrRs Is Nothing Then Set PrRs = Nothing
If Not PrDb Is Nothing Then Set PrDb = Nothing

' Check for count overwrite intenity data
If ProbeDataFileVersionNumber! > 8.28 And UseCountOverwriteIntensityDataFlag Then
Call DataCountOverwriteGet(samplerow%, sample())
If ierror Then Exit Sub
End If

' If fiducial data, load from Fiducial table
If sample(1).FiducialSetNumber% > 0 Then
Call DataFiducial(Int(1), sample(1).FiducialSetNumber%, sample(1).FiducialSetDescription$, sample(1).fiducialpositions!())
If ierror Then Exit Sub
End If

' Set background type flags (AllMANBgdFlag = true if all MAN, MANBgdFlag = true if any MAN)
sample(1).AllMANBgdFlag = True
sample(1).MANBgdFlag = False
For chan% = 1 To sample(1).LastElm%
If sample(1).BackgroundTypes%(chan%) = 1 Then  ' 0=off-peak, 1=MAN, 2=multipoint
sample(1).MANBgdFlag = True
Else
sample(1).AllMANBgdFlag = False
End If
Next chan%

' Load last arrays if data present and old version data file (defaults loaded in InitElement)
If ProbeDataFileVersionNumber! <= 4.82 Then
If sample(1).Datarows% > 0 Then
For chan% = 1 To sample(1).LastElm%
sample(1).LastOnCountTimes!(chan%) = sample(1).OnCountTimes!(sample(1).Datarows%, chan%)
sample(1).LastHiCountTimes!(chan%) = sample(1).HiCountTimes!(sample(1).Datarows%, chan%)
sample(1).LastLoCountTimes!(chan%) = sample(1).LoCountTimes!(sample(1).Datarows%, chan%)

' If unknown, modify for unknown count factors
If sample(1).Type% = 2 Then
If sample(1).UnknownCountFactors!(sample(1).Datarows%, chan%) = 0# Then
sample(1).UnknownCountFactors!(sample(1).Datarows%, chan%) = 1#
End If
sample(1).LastOnCountTimes!(chan%) = sample(1).OnCountTimes!(sample(1).Datarows%, chan%) / sample(1).UnknownCountFactors!(sample(1).Datarows%, chan%)
sample(1).LastHiCountTimes!(chan%) = sample(1).HiCountTimes!(sample(1).Datarows%, chan%) / sample(1).UnknownCountFactors!(sample(1).Datarows%, chan%)
sample(1).LastLoCountTimes!(chan%) = sample(1).LoCountTimes!(sample(1).Datarows%, chan%) / sample(1).UnknownCountFactors!(sample(1).Datarows%, chan%)
End If
sample(1).LastWaveCountTimes!(chan%) = DefaultWavescanCountTime!
sample(1).LastPeakCountTimes!(chan%) = DefaultPeakingCountTime!
sample(1).LastQuickCountTimes!(chan%) = DefaultQuickscanCountTime!
sample(1).LastCountFactors!(chan%) = sample(1).UnknownCountFactors!(sample(1).Datarows%, chan%)
sample(1).LastMaxCounts&(chan%) = sample(1).UnknownMaxCounts&(sample(1).Datarows%, chan%)
Next chan%
End If
End If

' Load the kilovolts array for normal samples
If ProbeDataFileVersionNumber! <= 4.89 Then
For chan% = 1 To sample(1).LastElm%
sample(1).TakeoffArray!(chan%) = sample(1).takeoff!
sample(1).KilovoltsArray!(chan%) = sample(1).kilovolts!
sample(1).BeamCurrentArray!(chan%) = sample(1).beamcurrent!
sample(1).BeamSizeArray!(chan%) = sample(1).beamsize!

sample(1).ColumnConditionMethodArray%(chan%) = sample(1).ColumnConditionMethod%
sample(1).ColumnConditionStringArray$(chan%) = sample(1).ColumnConditionString$
Next chan%
End If

' Calculate peak offsets (no warnings) for all samples
Call XrayGetOffsets(Int(1), sample())
If ierror Then Exit Sub

' Fix v. 5.21 bug for wavescan angstroms (data was saved without offset applied)
If ProbeDataFileVersionNumber! < 5.22 And sample(1).Type% = 3 Then
For chan% = 1 To sample(1).LastElm%
If sample(1).MotorNumbers%(chan%) > 0 Then
temp! = MotUnitsToAngstromMicrons!(sample(1).MotorNumbers%(chan%)) * (sample(1).Crystal2ds!(chan%) * (1# - sample(1).CrystalKs!(chan%))) / LIF2D!
For row% = 1 To sample(1).Datarows%
sample(1).LoPeakCounts!(row%, chan%) = (sample(1).HiPeakCounts!(row%, chan%) + sample(1).Offsets!(chan%)) * temp!
Next row%
End If
Next chan%
End If

' Load defaults for mag
If ProbeDataFileVersionNumber! <= 7.03 Then
If sample(1).magnificationanalytical! = 0# Then sample(1).magnificationanalytical! = DefaultMagnificationAnalytical!
If sample(1).magnificationimaging! = 0# Then sample(1).magnificationimaging! = DefaultMagnificationImaging!
End If

' Load defaults for aperture
If ProbeDataFileVersionNumber! <= 8.05 Then
If sample(1).ApertureNumber% = 0 Then sample(1).ApertureNumber% = DefaultAperture%
End If

' Load defaults for image shift
If ProbeDataFileVersionNumber! <= 8.11 Then
If sample(1).ImageShiftX! = 0# Then sample(1).ImageShiftX! = DefaultImageShiftX!
If sample(1).ImageShiftY! = 0# Then sample(1).ImageShiftY! = DefaultImageShiftY!
End If

' Load defaults for UnknownCountTimeForInterferenceStandardChanFlag for backward compatibility
If ProbeDataFileVersionNumber! <= 8.62 Then
If sample(1).Type% = 1 And sample(1).UnknownCountTimeForInterferenceStandardFlag Then
For chan% = 1 To sample(1).LastElm%
If AcquireIsUseUnknownCountTimeForInterferenceStandardFlag(chan%, sample()) Then
sample(1).UnknownCountTimeForInterferenceStandardChanFlag(chan%) = True
End If
Next chan%
End If
End If

' Load MPB last manual flags for backward compatibility (only if MPB acquisition or "shared" MPB (off-peak using MPB fit method))
If ProbeDataFileVersionNumber! < 11.39 Then
For chan% = 1 To sample(1).LastElm%
If sample(1).BackgroundTypes%(chan%) = 2 Or sample(1).OffPeakCorrectionTypes%(chan%) = MAXOFFBGDTYPES% Then

For m% = 1 To MAXMULTI%
If m% <= MAXMULTI_OLD% Or ProbeDataFileVersionNumber! >= 12.84 Then

If sample(1).Datarows% = 0 Then
If m% <= sample(1).MultiPointNumberofPointsAcquireHi%(chan%) Then
sample(1).MultiPointProcessLastManualFlagHi%(chan%, m%) = 0
End If
If m% <= sample(1).MultiPointNumberofPointsAcquireLo%(chan%) Then
sample(1).MultiPointProcessLastManualFlagLo%(chan%, m%) = 0
End If
Else
If m% <= sample(1).MultiPointNumberofPointsAcquireHi%(chan%) Then
sample(1).MultiPointProcessLastManualFlagHi%(chan%, m%) = sample(1).MultiPointProcessManualFlagHi%(sample(1).Datarows%, chan%, m%)
End If
If m% <= sample(1).MultiPointNumberofPointsAcquireLo%(chan%) Then
sample(1).MultiPointProcessLastManualFlagLo%(chan%, m%) = sample(1).MultiPointProcessManualFlagLo%(sample(1).Datarows%, chan%, m%)
End If
End If

End If
Next m%

End If
Next chan%
End If

' Load EDS spectral intensity data
If sample(1).EDSSpectraFlag Then
Call DataEDSSpectraGetData(samplerow%, sample)
If ierror Then Exit Sub
End If

' Load CL spectral intensity data
If sample(1).CLSpectraFlag Then
Call DataCLSpectraGetData(samplerow%, sample)
If ierror Then Exit Sub
End If

' Update status
'Call IOStatusAuto(vbNullString)
'Call AnalyzeStatusAnal(vbNullString)
'DoEvents

Exit Sub

' Errors
DataGetMDBSampleError:
Screen.MousePointer = vbDefault
MsgBox Error$ & ", reading sample " & SampleGetString$(samplerow%), vbOKOnly + vbCritical, "DataGetMDBSample"
ierror = True
Exit Sub

DataGetMDBSampleBadChannel:
Screen.MousePointer = vbDefault
msg$ = "Sample " & SampleGetString$(samplerow%) & " has an invalid element channel in " & ProbeDataFile$
MsgBox msg$, vbOKOnly + vbExclamation, "DataGetMDBSample"
ierror = True
Exit Sub

DataGetMDBSampleBadRow:
Screen.MousePointer = vbDefault
msg$ = "Sample " & SampleGetString$(samplerow%) & " has an invalid sample row in " & ProbeDataFile$
MsgBox msg$, vbOKOnly + vbExclamation, "DataGetMDBSample"
ierror = True
Exit Sub

DataGetMDBSampleBadIntegratedChannel:
Screen.MousePointer = vbDefault
msg$ = "Sample " & SampleGetString$(samplerow%) & " has an invalid element channel in " & ProbeDataFile$
MsgBox msg$, vbOKOnly + vbExclamation, "DataGetMDBSample"
ierror = True
Exit Sub

DataGetMDBSampleBadIntegratedRow:
Screen.MousePointer = vbDefault
msg$ = "Sample " & SampleGetString$(samplerow%) & " has an invalid sample row in " & ProbeDataFile$
MsgBox msg$, vbOKOnly + vbExclamation, "DataGetMDBSample"
ierror = True
Exit Sub

DataGetMDBSampleBadIntegratedIncrement:
Screen.MousePointer = vbDefault
msg$ = "Sample " & Format$(SampleNums%(samplerow%)) & " " & SampleNams$(samplerow%) & " has an invalid sample increment in " & ProbeDataFile$
MsgBox msg$, vbOKOnly + vbExclamation, "DataGetMDBSample"
ierror = True
Exit Sub

DataGetMDBSampleBadMultiPoint:
Screen.MousePointer = vbDefault
msg$ = "Sample " & Format$(SampleNums%(samplerow%)) & " " & SampleNams$(samplerow%) & " has an invalid sample multi-point in " & ProbeDataFile$
MsgBox msg$, vbOKOnly + vbExclamation, "DataGetMDBSample"
ierror = True
Exit Sub

End Sub
John J. Donovan, Pres. 
(541) 343-3400

"Not Absolutely Certain, Yet Reliable"

sem-geologist

#62
Quote from: John Donovan on March 27, 2025, 06:33:17 AMBy PfS do you mean Probe for EPMA? 
yes, sorry for misname.
Quote from: John Donovan on March 27, 2025, 06:33:17 AMThis is used because if an error occurs during a database write operation (e.g., computer crashes), the database automatically rolls back to the previous state. Similar to how money is transferred from one account to another!
Transactional write is not the unique feature of JET database. It is one of the base feature of most of relational database management systems based on SQL databases, be it single file (like SQLite) or distributed (like PostgreSQL, MariaDB, MySQL, Oracle database, MS SQL...). These compared with JET do not depend from file system (JET do some fishy write calls using NTFS - and it is main obstacle in Reverse Engineering and implementing fully functioning open source JET database engine) and can be easy migrated, cleaned up (database can be not only expanded, but also shrunken safely). Mentioned earlier open source tools for JET  (i.e. MDBTools) works with JET database OK only if no data were removed from the database... which JET does not do cleanly.

John Donovan

#63
Quote from: sem-geologist on March 28, 2025, 02:38:48 AM
Quote from: John Donovan on March 27, 2025, 06:33:17 AMThis is used because if an error occurs during a database write operation (e.g., computer crashes), the database automatically rolls back to the previous state. Similar to how money is transferred from one account to another!
Transactional write is not the unique feature of JET database. It is one of the base feature of most of relational database management systems based on SQL databases, be it single file (like SQLite) or distributed (like PostgreSQL, MariaDB, MySQL, Oracle database, MS SQL...).

I never claimed that transactional write was a unique feature of Jet. Only that this was one of several reasons why we liked using a database management system for data storage in Probe for EPMA.  I'm sure that some other database management system could be utilized in Probe for EPMA, but switching to a different one would be an enormous amount of work, and it would make all existing MDB Jet databases unreadable.

But since Jet still works in the latest Windows 11 operating system, we currently have backward compatibility going back to the early 1990s. That was my main point.

As for future compatibility, will that compatibility continue into the future?  I do not know, but there are a lot of Jet MDB databases out there in the world, so I'm hoping the answer is yes.

Writing software has always been "stepping into the stream" and hoping the current carries you with it. We've made lots of decisions about which components to utilize, e.g., our graphics library.

For example, we started with a product called Graphics Server (you can see in the older screen shots in this forum), but it was never updated to run properly in Windows 7 and later, so we had to "jump horses" in mid-stream to the Pro Essentials graphics library. Fortunately the choice of graphics library did not affect the data file management.

Another example is the choice of Internet tools.  We started with Catalyst Tools (for downloading CalcZAF and Probe for EPMA updates), and it's been a great choice, but late last year (as some of you may have noticed):

https://smf.probesoftware.com/index.php?topic=40.msg13206#msg13206

we started seeing many institutions locking down their Internet security even further, so we had to update to a more recent version of Catalyst that supports these newer protocols.

The "stream" never stops!    ;D
John J. Donovan, Pres. 
(541) 343-3400

"Not Absolutely Certain, Yet Reliable"