diff --git a/src/LIB/SURCOUCHE/src/mode_io_read_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_read_nc4.f90 index 8c68aeaf9138cd9e6b8c606d9c392ca1cbee87c3..f95effb73e96f12a5d95d213515dead022a548d6 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_read_nc4.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_read_nc4.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2022 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -1292,6 +1292,7 @@ CHARACTER(LEN=30) :: YVARNAME CHARACTER(LEN=:),ALLOCATABLE :: YSTR INTEGER(KIND=CDFINT) :: IDIMLEN INTEGER :: IDX,IRESP +REAL :: ZTIME CALL PRINT_MSG(NVERB_DEBUG,'IO','IO_Field_read_nc4_T0',TRIM(TPFILE%CNAME)//': reading '//TRIM(TPFIELD%CMNHNAME)) @@ -1312,7 +1313,7 @@ IF (istatus /= NF90_NOERR) CALL IO_Err_handle_nc4(istatus,'IO_Field_read_nc4_T0' IF (IDIMS == 0 .AND. (ITYPE == NF90_FLOAT .OR. ITYPE == NF90_DOUBLE) ) THEN ! Read time - istatus = NF90_GET_VAR(INCID, IVARID, TPDATA%xtime) + istatus = NF90_GET_VAR( INCID, IVARID, ZTIME ) IF (istatus /= NF90_NOERR) THEN CALL IO_Err_handle_nc4(istatus,'IO_Field_read_nc4_T0','NF90_GET_VAR',TRIM(YVARNAME),IRESP) GOTO 1000 @@ -1330,8 +1331,8 @@ IF (IDIMS == 0 .AND. (ITYPE == NF90_FLOAT .OR. ITYPE == NF90_DOUBLE) ) THEN ' read date is invalid') IRESP = -3 END IF - ! Correct date and time (necessary for example if time is bigger than 86400 s) - CALL DATETIME_CORRECTDATE(TPDATA) + ! Insert time + autocorrect date and time (necessary for example if time is bigger than 86400 s) + TPDATA = TPDATA + ZTIME ELSE CALL PRINT_MSG(NVERB_ERROR,'IO','IO_Field_read_nc4_T0',TRIM(TPFILE%CNAME)//': '//TRIM(YVARNAME)// & ' not read (wrong size or type)') diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 index 41fa69660654f7913ef4ebdfc059ed2b928e5ed7..85eab8c8ade9d1c217b72c669d0c42bae0041d1f 100644 --- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 +++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 @@ -1579,6 +1579,7 @@ use modd_time, only: tdtseg use modd_time_n, only: tdtcur use modd_type_date, only: date_time +use mode_datetime use mode_field, only: Find_field_id_from_mnhname use mode_gridproj, only: Sm_latlon use mode_nest_ll, only: Get_model_number_ll, Go_tomodel_ll @@ -2107,21 +2108,10 @@ if ( tzfile%lmaster ) then ! Do this correction only after computation of jte if ( jtb < 1 ) jtb = 1 - tzdates(jt)%nyear = tdtseg%nyear - tzdates(jt)%nmonth = tdtseg%nmonth - tzdates(jt)%nday = tdtseg%nday - tzdates(jt)%xtime = tdtseg%xtime + ( xles_times(jtb) + xles_times(jte) ) / 2. - !Not necessary: call Datetime_correctdate( tzdates(jt ) ) - - tzdates_bound(1, jt)%nyear = tdtseg%nyear - tzdates_bound(1, jt)%nmonth = tdtseg%nmonth - tzdates_bound(1, jt)%nday = tdtseg%nday - tzdates_bound(1, jt)%xtime = tdtseg%xtime + xles_times(jtb) + tzdates(jt) = tdtseg + ( xles_times(jtb) + xles_times(jte) ) / 2. - tzdates_bound(2, jt)%nyear = tdtseg%nyear - tzdates_bound(2, jt)%nmonth = tdtseg%nmonth - tzdates_bound(2, jt)%nday = tdtseg%nday - tzdates_bound(2, jt)%xtime = tdtseg%xtime + xles_times(jte) + tzdates_bound(1, jt) = tdtseg + xles_times(jtb) + tzdates_bound(2, jt) = tdtseg + xles_times(jte) end do call Write_time_coord( tzfile%tncdims%tdims(NMNHDIM_BUDGET_LES_AVG_TIME), 'time axis for LES budget time averages', & tzdates, tzdates_bound ) diff --git a/src/MNH/init_ground_paramn.f90 b/src/MNH/init_ground_paramn.f90 index bddb0a06e7fc570046ab0a5b03ea1ca7c77a9e6a..2d02a3fa10574d2e692a7376e5aaa8b2feb17ea9 100644 --- a/src/MNH/init_ground_paramn.f90 +++ b/src/MNH/init_ground_paramn.f90 @@ -195,9 +195,7 @@ END DO CALL FIND_FIELD_ID_FROM_MNHNAME('DTCUR',IID,IRESP) TZTCUR=>TFIELDLIST(IID)%TFIELD_T0D(1)%DATA ! -TZDATE = TZTCUR -TZDATE%xtime = TZDATE%xtime + NSTOP * XTSTEP -CALL DATETIME_CORRECTDATE(TZDATE) +TZDATE = TZTCUR + NSTOP * XTSTEP !Done field by field because TYPE(DATE) different in MesoNH and SURFEX TDATE_END%YEAR = TZDATE%nyear TDATE_END%MONTH = TZDATE%nmonth diff --git a/src/MNH/mode_datetime.f90 b/src/MNH/mode_datetime.f90 index 2328b0c938a0c87dc43e9d2adbd48e4ef7fabf8f..8f4d83c9961b1111c43f45490bde04dbf6015152 100644 --- a/src/MNH/mode_datetime.f90 +++ b/src/MNH/mode_datetime.f90 @@ -20,7 +20,6 @@ IMPLICIT NONE ! PRIVATE ! -PUBLIC :: DATETIME_DISTANCE, DATETIME_CORRECTDATE PUBLIC :: TPREFERENCE_DATE PUBLIC :: OPERATOR(<) PUBLIC :: OPERATOR(<=) diff --git a/src/MNH/mode_les_diachro.f90 b/src/MNH/mode_les_diachro.f90 index 9b20b01f48f24cb6baa1b4382ba81691cc54b1fe..697111c2f1cec2bb7a8b79ce90e2bd63bb0b726e 100644 --- a/src/MNH/mode_les_diachro.f90 +++ b/src/MNH/mode_les_diachro.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1994-2022 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -429,7 +429,7 @@ use modd_parameters, only: XUNDEF use modd_time, only: tdtseg use modd_type_date, only: date_time ! -use mode_datetime, only: Datetime_correctdate +use mode_datetime ! IMPLICIT NONE ! @@ -504,11 +504,7 @@ DO JAVG=1,IAVG END DO END DO - tpdates(javg)%nyear = tdtseg%nyear - tpdates(javg)%nmonth = tdtseg%nmonth - tpdates(javg)%nday = tdtseg%nday - tpdates(javg)%xtime = tdtseg%xtime + ( zles_temp_mean_start + zles_temp_mean_end ) / 2. - call Datetime_correctdate( tpdates(javg ) ) + tpdates(javg) = tdtseg + ( zles_temp_mean_start + zles_temp_mean_end ) / 2. END DO ! DEALLOCATE(PWORK6) @@ -529,7 +525,7 @@ use modd_les_n, only: nles_dtcount, nles_mean_start, nles_mean_end, nles_me use modd_time, only: tdtseg use modd_type_date, only: date_time -use mode_datetime, only: Datetime_correctdate +use mode_datetime implicit none @@ -573,11 +569,7 @@ do javg = 1, nles_mean_times end do end do - tpdates(javg)%nyear = tdtseg%nyear - tpdates(javg)%nmonth = tdtseg%nmonth - tpdates(javg)%nday = tdtseg%nday - tpdates(javg)%xtime = tdtseg%xtime + ( xles_times(jtb) + xles_times(jte) ) / 2. - call Datetime_correctdate( tpdates(javg) ) + tpdates(javg) = tdtseg + ( xles_times(jtb) + xles_times(jte) ) / 2. end do Deallocate( pwork4 ) diff --git a/src/MNH/modeln.f90 b/src/MNH/modeln.f90 index 695ad2415452089478b5fc6e5d03e5573ee39cef..09ddb79e686cf11af8f7a5f4b15583622f49fff4 100644 --- a/src/MNH/modeln.f90 +++ b/src/MNH/modeln.f90 @@ -2326,8 +2326,7 @@ XT_STEP_BUD = XT_STEP_BUD + ZTIME2 - ZTIME1 + XTIME_BU !* 27. CURRENT TIME REFRESH ! -------------------- ! -TDTCUR%xtime=TDTCUR%xtime + XTSTEP -CALL DATETIME_CORRECTDATE(TDTCUR) +TDTCUR = TDTCUR + XTSTEP ! !------------------------------------------------------------------------------- ! diff --git a/src/MNH/read_all_data_grib_case.f90 b/src/MNH/read_all_data_grib_case.f90 index 288544b8c0ada2ff58c28da7f7062af24fb880fc..f47205d60bce5ad7f444bc1e846e57e249da6f1f 100644 --- a/src/MNH/read_all_data_grib_case.f90 +++ b/src/MNH/read_all_data_grib_case.f90 @@ -1,4 +1,4 @@ -!MNH_LIC Copyright 1998-2023 CNRS, Meteo-France and Universite Paul Sabatier +!MNH_LIC Copyright 1998-2024 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC for details. version 1. @@ -1747,15 +1747,14 @@ CALL MPPDB_CHECK3D(XV_LS,"XV_LS",PRECISION) SELECT CASE (CSTEPUNIT) ! Time unit indicator CASE ('h') !hour - TPTCUR%xtime = TPTCUR%xtime + ITIMESTEP*3600. + TPTCUR = TPTCUR + ITIMESTEP * 3600. CASE ('m') !minute - TPTCUR%xtime = TPTCUR%xtime + ITIMESTEP*60. + TPTCUR = TPTCUR + ITIMESTEP * 60. CASE ('s') !minute - TPTCUR%xtime = TPTCUR%xtime + ITIMESTEP + TPTCUR = TPTCUR + REAL(ITIMESTEP) CASE DEFAULT WRITE (ILUOUT0,'(A,A,A)') ' | error CSTEPUNIT=',CSTEPUNIT, ' is different of s,m or h' END SELECT -CALL DATETIME_CORRECTDATE(TPTCUR) IF (HFILE(1:3)=='ATM') THEN CALL SM_PRINT_TIME(TPTCUR,TLUOUT0,'MESONH current date') TDTCUR = TPTCUR diff --git a/src/MNH/write_budget.f90 b/src/MNH/write_budget.f90 index d6d3247320da94b10b9e08f1899df68abd25f798..c4045f017869ba6755b1b8b32194b81e31714b20 100644 --- a/src/MNH/write_budget.f90 +++ b/src/MNH/write_budget.f90 @@ -133,7 +133,6 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv ) integer :: jsv ! loop index over the ksv svx logical, save :: gfirstcall = .true. logical :: gnocompress ! true: no compression along x and y direction (cart option) - real, dimension(:), allocatable :: zworktemp real, dimension(:,:,:,:,:,:), allocatable :: zrhodjn, zworkmask type(date_time), dimension(:), allocatable :: tzdates type(tfieldmetadata) :: tzfield @@ -195,20 +194,11 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv ) ! !* 2.1 Initialization ! - ALLOCATE( ZWORKTEMP(1) ) !Note: tzdates are used only in LFI files; for netCDF files, dates are written in the coordinates allocate( tzdates(1) ) ! !Compute time at the middle of the temporally-averaged budget timestep - !This time is computed from the beginning of the experiment - ZWORKTEMP(1) = TPDTCUR - TDTEXP + (1.-NBUSTEP*0.5) * PTSTEP - ! - tzdates(1)%nyear = tdtexp%nyear - tzdates(1)%nmonth = tdtexp%nmonth - tzdates(1)%nday = tdtexp%nday - tzdates(1)%xtime = tdtexp%xtime + zworktemp(1) - - DEALLOCATE ( ZWORKTEMP ) + tzdates(1) = TPDTCUR + (1.-NBUSTEP*0.5) * PTSTEP ! !------------------------------------------------------------------------------- ! @@ -216,25 +206,13 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv ) ! ----------- ! CASE('MASK') - ALLOCATE(ZWORKTEMP(nbusubwrite)) !Note: tzdates are used only in LFI files; for netCDF files, dates are written in the coordinates allocate( tzdates(nbusubwrite) ) ! - ZWORKTEMP(nbusubwrite) = TPDTCUR - TDTEXP + (1.-NBUSTEP*0.5) * PTSTEP - ! - tzdates(nbusubwrite)%nyear = tdtexp%nyear - tzdates(nbusubwrite)%nmonth = tdtexp%nmonth - tzdates(nbusubwrite)%nday = tdtexp%nday - tzdates(nbusubwrite)%xtime = tdtexp%xtime + zworktemp(nbusubwrite) + tzdates(nbusubwrite) = TPDTCUR + (1.-NBUSTEP*0.5) * PTSTEP DO JT=1,nbusubwrite-1 - ZWORKTEMP(JT) = ZWORKTEMP(nbusubwrite)-NBUSTEP*PTSTEP*(nbusubwrite-JT) - tzdates(jt)%nyear = tdtexp%nyear - tzdates(jt)%nmonth = tdtexp%nmonth - tzdates(jt)%nday = tdtexp%nday - tzdates(jt)%xtime = tdtexp%xtime + zworktemp(jt) + tzdates(jt) = TPDTCUR + (1.-NBUSTEP*0.5 - NBUSTEP*(nbusubwrite-JT)) * PTSTEP END DO - - DEALLOCATE( ZWORKTEMP ) ! !* 3.1 storage of the masks array !