Skip to content

Commit

Permalink
more ,etadata for Multio for computing monthly avarages
Browse files Browse the repository at this point in the history
  • Loading branch information
Dmitry Sidorenko committed Nov 15, 2023
1 parent 195185b commit 8e2e588
Show file tree
Hide file tree
Showing 2 changed files with 22 additions and 4 deletions.
10 changes: 9 additions & 1 deletion src/ifs_interface/iom.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,8 @@ MODULE iom
INTEGER :: step = 0
INTEGER :: currentDate, currentTime
INTEGER :: previousDate, previousTime
INTEGER :: startDate, startTime
INTEGER :: lastcounter
END TYPE

CONTAINS
Expand Down Expand Up @@ -390,9 +392,15 @@ SUBROUTINE iom_send_fesom_data(data)
cerr = md%set_int("currentTime", data%currentTime)
cerr = md%set_int("previousDate", data%previousDate)
cerr = md%set_int("previousTime", data%previousTime)
cerr = md%set_int("startDate", data%startDate)
cerr = md%set_int("startTime", data%startTime)
cerr = md%set_int("sampleInterval", data%sampleInterval)
cerr = md%set_int("sampleIntervalInSeconds", data%sampleInterval)
! cerr = md%set_int("sampleIntervalInSeconds", data%sampleInterval)
cerr = md%set_string("sampleIntervalUnit", 'S')
cerr = md%set_int("sampleIntervalInSeconds", data%sampleInterval)
cerr = md%set_int("timeStep", data%sampleInterval) !we do not distinguish between the timestep & sampling interval legacy code for MULTIO
cerr = md%set_int("step-frequency", data%lastcounter)
cerr = md%set_int("step", data%step)
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_data: md%set_int(date) failed: ', multio_error_string(cerr))
END IF
Expand Down
16 changes: 13 additions & 3 deletions src/io_meandata.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,8 @@ module io_MEANDATA
real(real32), allocatable, dimension(:,:) :: local_values_r4
real(real64), allocatable :: aux_r8(:)
real(real32), allocatable :: aux_r4(:)
integer :: addcounter=0
integer :: addcounter =0
integer :: lastcounter=0 ! before addcounter is set to 0
real(kind=WP), pointer :: ptr3(:,:) ! todo: use netcdf types, not WP
character(500) :: filename
character(100) :: name
Expand Down Expand Up @@ -56,9 +57,10 @@ module io_MEANDATA
! to be passed to MULTIO (time window for the accumulations)
integer :: currentDate, currentTime
integer :: previousDate, previousTime
integer :: startDate, startTime
contains
final destructor
end type
end type
!
!--------------------------------------------------------------------------------------------
!
Expand Down Expand Up @@ -1287,6 +1289,7 @@ subroutine output(istep, ice, dynamics, tracers, partit, mesh)
!$OMP END PARALLEL DO
end if ! --> if (entry%accuracy == i_real8) then
!___________________________________________________________________
entry%lastcounter=entry%addcounter
entry%addcounter = 0 ! clean_meanarrays
entry%ctime_copy = ctime

Expand Down Expand Up @@ -1405,6 +1408,8 @@ subroutine def_stream3D(glsize, lcsize, name, description, units, data, freq, fr
entry%previousTime=-1
entry%currentDate=yearold * 10000 + month * 100 + day_in_month
entry%currentTime=INT(INT(timeold / 3600) * 10000 + (INT(timeold / 60) - INT(timeold / 3600) * 60) * 100 + (timeold-INT(timeold / 60) * 60))
entry%startDate=entry%currentDate
entry%startTime=entry%currentTime
!___________________________________________________________________________
! fill up 3d meandata streaming object
! 3d specific
Expand Down Expand Up @@ -1482,7 +1487,9 @@ subroutine def_stream2D(glsize, lcsize, name, description, units, data, freq, fr
entry%previousDate=-1
entry%previousTime=-1
entry%currentDate=yearold * 10000 + month * 100 + day_in_month
entry%currentTime=INT(INT(timeold / 3600) * 10000 + (INT(timeold / 60) - INT(timeold / 3600) * 60) * 100 + (timeold-INT(timeold / 60) * 60))
entry%currentTime=INT(INT(timeold / 3600) * 10000 + (INT(timeold / 60) - INT(timeold / 3600) * 60) * 100 + (timeold-INT(timeold / 60) * 60))
entry%startDate=entry%currentDate
entry%startTime=entry%currentTime
!___________________________________________________________________________
! fill up 3d meandata streaming object
! 2d specific
Expand Down Expand Up @@ -1755,6 +1762,9 @@ SUBROUTINE send_data_to_multio(entry)
request%previousTime=entry%previousTime
request%currentDate =entry%currentDate
request%currentTime =entry%currentTime
request%startDate =entry%startDate
request%startTime =entry%startTime
request%lastcounter =entry%lastcounter
request%sampleInterval=INT(dt)

IF (.NOT. entry%is_elem_based) THEN
Expand Down

0 comments on commit 8e2e588

Please sign in to comment.