program DataFile2CVS ! This program reads and outputs some of the *.dat file into a csv file for amCharts.com output. ! 12 May 2011 V 1.0 First writing ! 17 Jul 2015 V 2.0 Just modifying a bit for the A2M project ! 29-Oct-2018 V 3.0 Modified for DEB project. For unknown reasons, the DO probe sometimes give 0 mA readings, ! which the monitor program now assigns a value of -1. So, to work with HighCharts, that value needs ! to be assigned a a value of null ! 12-Nov-2018 V 4.0: Have added code to also produce a second file that has the high resolution pH and DO data ! from the Hamilton modbus files. implicit none ! Local declarations integer tempUnit ! unit that is temporarily opened integer datUnit ! File unit of *.dat file integer cvsUnit ! file unit for the CVS output file. integer nColRead ! Number of columns to read in from the *.dat file. integer, parameter:: maxCol = 1000 ! maximum number of columns that can be read from *.dat file. character filename*80, cvsStr*1000, str*100, inpFile*80 integer, parameter:: nullLen = 8 character(nullLen), parameter:: numStr = '-1.00000' ! This is the value in the data file that should be replaced with null character(nullLen), parameter:: nulStr = '' ! This will remove the data from the column (if you use "null", then a scatter plot results) integer indx character(5000) strRec ! this needs to be long enough to hold the entire CVS output string integer narg, nstat, i, iovar, ifail real(8) datRec(maxCol) character fmtStr*50 ! This variables are optained from the inputfile that is read in via a namelist ! which is called "input" character cvsFile*80, datFile*80 integer nRowSkip ! number of columns to be read and rows to be skipped in *.dat file integer nselcol, selCol(maxCol) ! the number of columns and colunmns to be extracted from *.dat file character names(maxCol)*20 ! This assigns the names to the nselcol columns to be created in the csv file namelist /input4CVS/ cvsFile, datFile, nRowSkip, nselcol, selCol, names write(*,'(a)') 'Program version 4.0 (12-Nov-2018)' ! Read from the command line (if possible) the input file (using something with a *.inp extenstion probably) narg = 1 Call Getarg (narg, inpFile, nstat) If (nstat .Lt. 0) Then Write(6,'(1x,a,$)') 'Enter input filename: ' Read(5,'(a)') inpFile End If ! open the namelist input file and read in variables selCol = 0 ! initial all values to zero. open(newunit=tempUnit,file=trim(inpFile),status='old') read(tempUnit,nml=input4CVS) close(unit=tempUnit) ! Get the maximumn colmns that need to read from the *.dat file nColRead = maxval(selCol) ! open *.dat file open(newunit=datUnit,file=trim(datFile),status='old', action='read') ! open the cvs output file for amCharts plots open(newunit=cvsUnit,file=trim(cvsFile),status='unknown') ! Write names as first record str = '(####(a))' write(str(2:5),'(i4)') nselcol write(cvsUnit,str) (trim(names(i))//', ',i=1,nselcol-1), trim(names(nselcol)) ! skip the first nRowSkip records do i=1,nRowSkip read(datUnit,'(a)') filename end do ! ************ Main reading loop ************* fmtStr = '(f12.6,####('','',g13.6))' write(fmtStr(8:11),'(i4)') nselCol-1 do read(datUnit,*,iostat=iovar) (datRec(i),i=1,nColRead) if (iovar /= 0) exit ! at end of file, exit ! write desired columns to a long string that can then be parsed for -1.000000 write(strRec,fmtStr) (datRec(selCol(i)),i=1,nselCol) ! replace any occurance of -1.000000 with null do indx = index(strRec, numStr) if (indx == 0) exit strRec(indx:indx+nullLen-1) = nulStr end do write(cvsUnit,'(a)') trim(strRec) end do ! *********** End of main reading loop ****** close(unit=datUnit) close(unit=cvsUnit) ! Generate a CSV files for DO and pH from Hamilton Trace files call DOpH2CSV(inpFile) stop end program DataFile2CVS subroutine DOpH2CSV(inpFile) ! This routine creats a CSV file fromt the Hamilton trace files ! This routine is not very efficient, because it recreates the CSV file for Highcharts ! from all the trace files each time. ! It also assumes that how the files are read by getfileinfoQQ is the correct time order, which ! I think is true. use ifport ! need portability functions to get filesnames, etc. implicit none character(len=*), intent(in):: inpFile ! The *.inp file that has the DOpH namelist ! local declarations integer i integer tempUnit, csvUnit, io character(180) probeDir ! full directory name of where the probe trace files are located. integer, parameter:: maxProbes = 10 ! this is the maximum number of probes that can be read integer noProbes ! number of probes to read trace files for character(20) probeID(maxProbes,2) ! This is the hamilton name, like pH_243632-2353-1178, and name, like MC1 pH integer tmpUnit(maxProbes) ! used for scratch files created for each probe. ! Some declarations needed to get files using ifport routines integer nameLen ! this is the character lenght of a filename, if found integer(kind=int_ptr_kind()) handle type(file$info) traceFileInfo ! see GETFILEINFOQQ for info character(255) longStr character(15) timeStr, valueStr real(4) expTime, value real(8) tzero ! the calculated julian starting time character(10) t0string ! This is the string used to convert to julian day tzero, must be" YYYY-MM-DD integer t0year, t0month, t0day, ifail character(80) DOpHfileCSV ! name of CSV to store DO and pH data. ! namelist DOpH namelist /DOpH/ probeDir, noProbes, probeID, t0string, DOpHfileCSV ! open the namelist input file and read in variables for DO and pH open(newunit=tempUnit,file=trim(inpFile),status='old') read(tempUnit,nml=DOpH) close(unit=tempUnit) if (noProbes > maxProbes) then write(*,'(a,i2,a)') 'Maximum number of probes set to ', maxProbes, '. Recompile program.' return end if ! Set the tzero time based on year, month and day ! Set time zero based on above date. This will be used to ease tecplot graphing read(t0string(1:4 ),*) t0year read(t0string(6:7 ),*) t0month read(t0string(9:10),*) t0day call julday(t0year,t0month,t0day,0,0,0.0,tzero,ifail) ! Begin loop reading trace file to append to CSV file do i=1,noProbes ! open a scratch file to save the probe data in. This will be then copied to the CSV file open(newunit=tmpUnit(i), status='scratch', form='unformatted') ! creat the while chard name to search for longStr = trim(probeDir)//'\*'//trim(probeID(i,1))//'.txt' handle = file$first do nameLen = getfileinfoQQ(longStr, traceFileInfo, handle) if (handle == file$last .or. handle == file$error) exit ! all of the files have been found (or an error occured) call readTraceFile(probeDir, traceFileInfo%name, tmpUnit(i), tzero) end do end do ! Copy the data in the scratch files to the named CSV file. open(newunit=csvUnit, file=trim(DOpHfileCSV), status='unknown') ! This file will be over written ! write the header to the CSV file longStr = 'Time (d), '//trim(probeID(1,2)) do i=2,noProbes longStr = trim(longStr)//', Time (d), '//trim(probeID(i,2)) end do write(csvUnit,'(a)') trim(longStr) ! rewind all the units do i=1,noProbes rewind(tmpUnit(i), iostat=io) end do ! write the data in the temp files to the CSV file outer: do read(tmpUnit(1), iostat=io) expTime, value if (io /= 0) exit outer ! exit as soon as any of the files run out of data write(timeStr,'(f11.6)') expTime write(valueStr,'(f5.2)') value longStr = trim(timeStr)//', '//trim(valueStr) do i=2,noProbes read(tmpUnit(i), iostat=io) expTime, value if (io /= 0) exit outer ! exit as soon as any of the files run out of data write(timeStr,'(f11.6)') expTime write(valueStr,'(f5.2)') value longStr = trim(longStr)//', '//trim(timeStr)//', '//trim(valueStr) end do write(csvUnit,'(a)') trim(longStr) end do outer ! close all the temp files do i=1,noProbes close(tmpUnit(i)) end do close(csvUnit) return end subroutine DOpH2CSV subroutine readTraceFile(probeDir, traceFileName, sUnit, tzero) ! This routine reads a Hamilton Probe trace file and writes the time and variable value to the ! scratch file already opened on unit implicit none character(*), intent(in):: probeDir ! full directory name to data character(*), intent(in):: traceFileName ! Name of the trace file to open and read integer , intent(in):: sUnit ! scratch unit to write data to real(8) , intent(in):: tzero ! numerical value of julian day to base t zero on. ! local declarations integer tUnit, io character(255) line integer year, month, day, hour, min, ifail real(4) sec real(8) jtime real(4) value, temp ! open the trace file open(newunit=tUnit, file=trim(probeDir)//'\'//trim(traceFileName), readonly, status='old') do read(tUnit,'(a)',iostat=io) line if (io /= 0) exit ! either an EOF or error occured, so done reading file ! This first 4 characters of a record should be the year, if not, skip the line if (verify(line(1:4),'0123456789') /= 0) cycle read(line (1: 4),*) year read(line( 6: 7),*) month read(line( 9:10),*) day read(line(12:13),*) hour read(line(15:16),*) min read(line(18:19),*) sec call julday(year, month, day, hour, min, sec, jtime, ifail) read(line(21:),*) value, temp ! note, not saving temperature. write(sUnit) real(jtime-tzero), value end do close(tUnit) return end subroutine readTraceFile