- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I have a table of daily data for 50 years (18262 data values), which I am able to read and write into an output file. I have another table of coefficients, which is actually yearly (50 data values). I would like to multiply the yearly coefficients with the 18262 data values, whenever the year matches.
Basically, I am looking for relating two arrays when they match (as I am trying to do from line 41 to 45 in the attached program). Attached herewith are also the two tables.
I am sorry if I am asking this same question many times, but this is the place I feel that I really need help with to move forward. Any ideas or suggestions to multiply the correct coefficient value (coeff(n,2) with tc to get the modified table of 18262 data values, would be greatly helpful to me.
Thank you.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Dear bhvj,
since the dates are ascendingly ordered, you could simply loop through the tc-data per year and localize the data rowns at the beginning and end of each year. Then, you multiply all that data with the respective coefficient of that year (in one chunk, which is faster than element-wise).
Example:
PROGRAM tc_test USE, INTRINSIC :: ISO_FORTRAN_ENV ! IMPLICIT NONE ! Declarations INTEGER, ALLOCATABLE :: iyr(:),imonth(:),iday(:) REAL, ALLOCATABLE :: tc(:),tc_out(:),tc_mod(:) INTEGER, PARAMETER :: i_max =50 INTEGER, PARAMETER :: j_max =3 REAL :: coeff(i_max,j_max) INTEGER :: year(i_max), n(50) INTEGER :: nd,i,j,k,filend,ALLOC_ERR ! NEW ------------------------------------------------------ integer :: cc_year, ii_year, ii_year_next ! END NEW -------------------------------------------------- ! OPEN(unit=20,file='tc.dat',status='old') nd=-1 filend=0 READ(20,*) DO WHILE(filend.ne.IOSTAT_END) READ(20,*,iostat=filend) nd=nd+1 END DO print*, nd, 'Data pairs read' ALLOCATE (iyr(nd),imonth(nd),iday(nd),tc(nd),tc_out(nd), &tc_mod(nd)) REWIND(20) READ(20,*) DO i=1,nd READ(20,*)iyr(i),imonth(i),iday(i),tc(i) END DO tc_out = 0.5*tc CLOSE(20) ! Reading tc_coeff table OPEN (9,file='tc_coeff.dat',status='old') READ (9, *) DO i=1,50 READ(9,*) year(i), (coeff(i,k), k=1,3) END DO print*,'coeff(49,2)=',coeff(49,2) ! Corrected tc ! DO i=1,nd ! DO WHILE (iyr(i) .EQ. n(i)) ! tc_mod=coeff(n,2)*tc ! END DO ! END DO ! NEW ------------------------------------------------------ ! Multiply tc-data with year-wise coeffs ii_year = 1 ! first index of tc-data of current year coeff_loop: do cc_year = 1, 50 ! Locate all tc-data of current year ! (assume ascendingly ordered tc-years) ii_year_next = ii_year + 1 ! first index of tc-data of next year do if (ii_year_next > nd) exit if (iyr(ii_year_next) > iyr(ii_year)) exit ii_year_next = ii_year_next + 1 end do ! Multiply all tc-data of current year with respective coeff tc_mod(ii_year:ii_year_next-1) = & tc(ii_year:ii_year_next-1) * coeff(cc_year,2) ! Continue scaling tc-data of next year ii_year = ii_year_next end do coeff_loop ! END NEW -------------------------------------------------- ! OPEN(unit=30,file='tc_out.dat',status='new') DO i=1,nd WRITE(30,*)iyr(i),imonth(i),iday(i),tc_out(i) END DO DEALLOCATE (iyr,imonth,iday,tc,tc_out, &tc_mod, STAT = ALLOC_ERR) END PROGRAM tc_test
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you very much for Ferdinand, for the code and for suggestion for the efficient way of doing this. I have understood it, implemented it and it now works fine. Thanks again for the timely help which will now help me forward.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Great! When thinking about it again, here is a simpler solution, closer to your original & it does not rely on the order of the tc-data. Instead it relies on the fact that the coeffs are indexed by the linear sequence [first_year, first_year+1, ..., last_year] over the years. It might be a little less efficient though.
! Corrected tc: ! Multiply tc-data with coeff's of tc-years DO i=1,nd ! Index of the coeff assocaited with tc-year j = iyr(i) - iyr(1) + 1 ! Multiply tc-data with associated coeff tc_mod(i) = tc(i) * coeff(j,2) END DO
The table-lookup is a mere index-shift (line 5 in snippet).
EDIT: corrected error in line 7
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you very much once again, Ferdinand for your detailed explanation and the alternate solution. I have understood it, implemented it and this works fine too.

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page