Skip to content
Snippets Groups Projects
Commit 5e1734d6 authored by WAUTELET Philippe's avatar WAUTELET Philippe
Browse files

Philippe 14/01/2021: budgets: tpdates dummy argument not necessary for Write_diachro_nc4

parent f4481557
No related branches found
No related tags found
No related merge requests found
...@@ -184,6 +184,7 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv ) ...@@ -184,6 +184,7 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
!* 2.1 Initialization !* 2.1 Initialization
! !
ALLOCATE( ZWORKTEMP(1) ) ALLOCATE( ZWORKTEMP(1) )
!Note: tzdates are used only in LFI files; for netCDF files, dates are written in the coordinates
allocate( tzdates(1) ) allocate( tzdates(1) )
! !
!Compute time at the middle of the temporally-averaged budget timestep !Compute time at the middle of the temporally-averaged budget timestep
...@@ -206,6 +207,7 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv ) ...@@ -206,6 +207,7 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
! !
CASE('MASK') CASE('MASK')
ALLOCATE(ZWORKTEMP(nbusubwrite)) ALLOCATE(ZWORKTEMP(nbusubwrite))
!Note: tzdates are used only in LFI files; for netCDF files, dates are written in the coordinates
allocate( tzdates(nbusubwrite) ) allocate( tzdates(nbusubwrite) )
! !
CALL DATETIME_DISTANCE(TDTEXP,TPDTCUR,ZWORKTEMP(nbusubwrite)) CALL DATETIME_DISTANCE(TDTEXP,TPDTCUR,ZWORKTEMP(nbusubwrite))
......
...@@ -103,7 +103,7 @@ IMPLICIT NONE ...@@ -103,7 +103,7 @@ IMPLICIT NONE
TYPE(TFILEDATA), INTENT(IN) :: TPDIAFILE ! file to write TYPE(TFILEDATA), INTENT(IN) :: TPDIAFILE ! file to write
class(tfield_metadata_base), dimension(:), intent(in) :: tpfields class(tfield_metadata_base), dimension(:), intent(in) :: tpfields
CHARACTER(LEN=*), INTENT(IN) :: HGROUP, HTYPE CHARACTER(LEN=*), INTENT(IN) :: HGROUP, HTYPE
type(date_time), dimension(:), intent(in) :: tpdates type(date_time), dimension(:), intent(in) :: tpdates !Used only for LFI files
REAL, DIMENSION(:,:,:,:,:,:), INTENT(IN) :: PVAR REAL, DIMENSION(:,:,:,:,:,:), INTENT(IN) :: PVAR
LOGICAL, INTENT(IN), OPTIONAL :: OICP, OJCP, OKCP LOGICAL, INTENT(IN), OPTIONAL :: OICP, OJCP, OKCP
INTEGER, INTENT(IN), OPTIONAL :: KIL, KIH INTEGER, INTENT(IN), OPTIONAL :: KIL, KIH
...@@ -152,7 +152,7 @@ if ( tpdiafile%cformat == 'LFI' .or. tpdiafile%cformat == 'LFICDF4' ) & ...@@ -152,7 +152,7 @@ if ( tpdiafile%cformat == 'LFI' .or. tpdiafile%cformat == 'LFICDF4' ) &
#ifdef MNH_IOCDF4 #ifdef MNH_IOCDF4
if ( tpdiafile%cformat == 'NETCDF4' .or. tpdiafile%cformat == 'LFICDF4' ) & if ( tpdiafile%cformat == 'NETCDF4' .or. tpdiafile%cformat == 'LFICDF4' ) &
call Write_diachro_nc4( tpdiafile, tpfields, hgroup, htype, tpdates, pvar, gicp, gjcp, gkcp, kil, kih, kjl, kjh, kkl, kkh, & call Write_diachro_nc4( tpdiafile, tpfields, hgroup, htype, pvar, gicp, gjcp, gkcp, kil, kih, kjl, kjh, kkl, kkh, &
osplit, tpflyer ) osplit, tpflyer )
#endif #endif
...@@ -625,7 +625,7 @@ end subroutine Write_diachro_lfi ...@@ -625,7 +625,7 @@ end subroutine Write_diachro_lfi
#ifdef MNH_IOCDF4 #ifdef MNH_IOCDF4
!----------------------------------------------------------------------------- !-----------------------------------------------------------------------------
subroutine Write_diachro_nc4( tpdiafile, tpfields, hgroup, htype, tpdates, pvar, oicp, ojcp, okcp, kil, kih, kjl, kjh, kkl, kkh, & subroutine Write_diachro_nc4( tpdiafile, tpfields, hgroup, htype, pvar, oicp, ojcp, okcp, kil, kih, kjl, kjh, kkl, kkh, &
osplit, tpflyer ) osplit, tpflyer )
use NETCDF, only: NF90_DEF_DIM, NF90_DEF_GRP, NF90_DEF_VAR, NF90_INQ_NCID, NF90_PUT_ATT, NF90_PUT_VAR, & use NETCDF, only: NF90_DEF_DIM, NF90_DEF_GRP, NF90_DEF_VAR, NF90_INQ_NCID, NF90_PUT_ATT, NF90_PUT_VAR, &
...@@ -647,7 +647,6 @@ use mode_io_tools_nc4, only: IO_Err_handle_nc4 ...@@ -647,7 +647,6 @@ use mode_io_tools_nc4, only: IO_Err_handle_nc4
type(tfiledata), intent(in) :: tpdiafile ! File to write type(tfiledata), intent(in) :: tpdiafile ! File to write
class(tfield_metadata_base), dimension(:), intent(in) :: tpfields class(tfield_metadata_base), dimension(:), intent(in) :: tpfields
character(len=*), intent(in) :: hgroup, htype character(len=*), intent(in) :: hgroup, htype
type(date_time), dimension(:), intent(in) :: tpdates
real, dimension(:,:,:,:,:,:), intent(in) :: pvar real, dimension(:,:,:,:,:,:), intent(in) :: pvar
logical, intent(in) :: oicp, ojcp, okcp logical, intent(in) :: oicp, ojcp, okcp
integer, intent(in), optional :: kil, kih integer, intent(in), optional :: kil, kih
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment