Skip to content

Commit

Permalink
after meeting with Philipp & Razvan we came up with the changes which…
Browse files Browse the repository at this point in the history
… are required for the proper data governance in FESOM/IFS/MULTIO setup
  • Loading branch information
Dmitry Sidorenko committed Nov 9, 2023
1 parent 98b6b8c commit 220202d
Show file tree
Hide file tree
Showing 2 changed files with 41 additions and 29 deletions.
39 changes: 15 additions & 24 deletions src/ifs_interface/iom.F90
Original file line number Diff line number Diff line change
Expand Up @@ -30,11 +30,14 @@ MODULE iom
TYPE iom_field_request
CHARACTER(100) :: name = REPEAT(" ", 100)
CHARACTER(100) :: category = REPEAT(" ", 100)
CHARACTER(5) :: gridType = REPEAT(" ", 5)
CHARACTER(6) :: gridType = REPEAT(" ", 6)
REAL(real64), DIMENSION(:), POINTER :: values => NULL()
INTEGER :: globalSize = 0
INTEGER :: sampleInterval=0
INTEGER :: level = 0
INTEGER :: step = 0
INTEGER :: currentDate, currentTime
INTEGER :: previousDate, previousTime
END TYPE

CONTAINS
Expand Down Expand Up @@ -247,7 +250,7 @@ SUBROUTINE iom_send_fesom_domains(partit, mesh)
CALL ctl_stop('send_fesom_domains: ngrid, md%new() failed: ', multio_error_string(cerr))
END IF

cerr = md%set_string("name", "ngrid")
cerr = md%set_string("name", "N grid")
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_domains: ngrid, md%set_string(name) failed: ', multio_error_string(cerr))
END IF
Expand Down Expand Up @@ -289,7 +292,7 @@ SUBROUTINE iom_send_fesom_domains(partit, mesh)
CALL ctl_stop('send_fesom_domains: egrid, md%new() failed: ', multio_error_string(cerr))
END IF

cerr = md%set_string("name", "egrid")
cerr = md%set_string("name", "C grid")
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_domains: egrid, md%set_string(name) failed: ', multio_error_string(cerr))
END IF
Expand Down Expand Up @@ -363,12 +366,12 @@ SUBROUTINE iom_send_fesom_data(data)
CALL ctl_stop('send_fesom_data: md%set_string(name) failed: ', multio_error_string(cerr))
END IF

cerr = md%set_string("gridSubtype", "undefined")
cerr = md%set_string("gridSubtype", data%gridType)
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_data: md%set_string(gridSubType) failed: ', multio_error_string(cerr))
END IF

cerr = md%set_string("grid-type", "undefined")
cerr = md%set_string("gridType", "CORE2")
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_data: md%set_string(grid-type) failed: ', multio_error_string(cerr))
END IF
Expand All @@ -383,25 +386,13 @@ SUBROUTINE iom_send_fesom_data(data)
CALL ctl_stop('send_fesom_data: md%set_string(domain) failed: ', multio_error_string(cerr))
END IF

cerr = md%set_int("step", data%step)
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_data: md%set_int(step) failed: ', multio_error_string(cerr))
END IF

cerr = md%set_int("stepInHours", data%step*24)
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_data: md%set_int(stepInHours) failed: ', multio_error_string(cerr))
END IF

cerr = md%set_int("timeSpanInHours", 24)
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_data: md%set_int(timeSpanInHours) failed: ', multio_error_string(cerr))
END IF

cerr = md%set_int("currentDate", yearnew * 10000 + month * 100 + day_in_month)
cerr = md%set_int("currentTime", INT(INT(timenew / 3600) * 10000 + (INT(timenew / 60) - INT(timenew / 3600) * 60) * 100 + (timenew-INT(timenew / 60) * 60)))
cerr = md%set_int("startDate", 2020 * 10000 + 01 * 100 + 20)
cerr = md%set_int("startTime", 0)
cerr = md%set_int("currentDate", data%currentDate)
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("sampleInterval", data%sampleInterval)
cerr = md%set_int("sampleIntervalInSeconds", data%sampleInterval)
cerr = md%set_string("sampleIntervalUnit", 'S')
IF (cerr /= MULTIO_SUCCESS) THEN
CALL ctl_stop('send_fesom_data: md%set_int(date) failed: ', multio_error_string(cerr))
END IF
Expand Down
31 changes: 26 additions & 5 deletions src/io_meandata.F90
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module io_MEANDATA
USE MOD_PARTIT
USE MOD_PARSUP
USE g_clock
use o_PARAM, only : WP
use, intrinsic :: iso_fortran_env, only: real64, real32
use io_data_strategy_module
Expand Down Expand Up @@ -52,6 +53,9 @@ module io_MEANDATA
real(real32), allocatable, dimension(:,:) :: local_values_r4_copy
real(kind=WP) :: ctime_copy
integer :: mype_workaround
! to be passed to MULTIO (time window for the accumulations)
integer :: currentDate, currentTime
integer :: previousDate, previousTime
contains
final destructor
end type
Expand Down Expand Up @@ -1397,7 +1401,10 @@ subroutine def_stream3D(glsize, lcsize, name, description, units, data, freq, fr
!___________________________________________________________________________
! initialise meandata streaming object
call associate_new_stream(name, entry)

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))
!___________________________________________________________________________
! fill up 3d meandata streaming object
! 3d specific
Expand Down Expand Up @@ -1472,7 +1479,10 @@ subroutine def_stream2D(glsize, lcsize, name, description, units, data, freq, fr
!___________________________________________________________________________
! initialise meandata streaming object
call associate_new_stream(name, entry)

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))
!___________________________________________________________________________
! fill up 3d meandata streaming object
! 2d specific
Expand Down Expand Up @@ -1726,7 +1736,7 @@ subroutine io_r2g(n, partit, mesh)
SUBROUTINE send_data_to_multio(entry)
USE iom
USE multio_api

IMPLICIT NONE

TYPE(Meandata), TARGET, INTENT(INOUT) :: entry
Expand All @@ -1738,10 +1748,21 @@ SUBROUTINE send_data_to_multio(entry)
globalSize = entry%glsize(2)

request%name = trim(entry%name)
entry%previousDate=entry%currentDate
entry%previousTime=entry%currentTime
entry%currentDate=yearnew * 10000 + month * 100 + day_in_month
entry%currentTime=INT(INT(timenew / 3600) * 10000 + (INT(timenew / 60) - INT(timenew / 3600) * 60) * 100 + (timenew-INT(timenew / 60) * 60))

request%previousDate=entry%previousDate
request%previousTime=entry%previousTime
request%currentDate =entry%currentDate
request%currentTime =entry%currentTime
request%sampleInterval=INT(dt)

IF (.NOT. entry%is_elem_based) THEN
request%gridType = "ngrid"
request%gridType = "N grid"
ELSE
request%gridType = "egrid"
request%gridType = "C grid"
END IF
request%globalSize = globalSize
request%step = entry%rec_count
Expand Down

0 comments on commit 220202d

Please sign in to comment.