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

Philippe 16/12/2020: minor: rename xles_dates -> tles_dates

parent ffa3ca9f
No related branches found
No related tags found
No related merge requests found
...@@ -318,7 +318,7 @@ NLES_TCOUNT = 0 ...@@ -318,7 +318,7 @@ NLES_TCOUNT = 0
!* 3.6 dates array for diachro !* 3.6 dates array for diachro
! ---------------------- ! ----------------------
! !
allocate( xles_dates( nles_times ) ) allocate( tles_dates( nles_times ) )
allocate( xles_times( nles_times ) ) allocate( xles_times( nles_times ) )
! !
!* 3.7 No data !* 3.7 No data
......
...@@ -145,8 +145,8 @@ NLES_TCOUNT = NLES_TCOUNT + 1 ...@@ -145,8 +145,8 @@ NLES_TCOUNT = NLES_TCOUNT + 1
! !
NLES_CURRENT_TCOUNT = NLES_TCOUNT NLES_CURRENT_TCOUNT = NLES_TCOUNT
! !
xles_dates(nles_tcount ) = tdtcur tles_dates(nles_tcount) = tdtcur
call Datetime_distance( tdtseg, tdtcur, xles_times(nles_tcount ) ) call Datetime_distance( tdtseg, tdtcur, xles_times(nles_tcount) )
! !
!* forward-in-time time-step !* forward-in-time time-step
! !
......
...@@ -64,7 +64,7 @@ TYPE LES_t ...@@ -64,7 +64,7 @@ TYPE LES_t
INTEGER :: NSPECTRA_NI ! number of wave lengths in I direction INTEGER :: NSPECTRA_NI ! number of wave lengths in I direction
INTEGER :: NSPECTRA_NJ ! number of wave lengths in J direction INTEGER :: NSPECTRA_NJ ! number of wave lengths in J direction
! !
type(date_time), dimension(:), pointer :: xles_dates => null() !Dates array type(date_time), dimension(:), pointer :: tles_dates => null() !Dates array
real, dimension(:), pointer :: xles_times => null() !Times from the start of the segment real, dimension(:), pointer :: xles_times => null() !Times from the start of the segment
! !
REAL, DIMENSION(:), POINTER :: XLES_Z=>NULL() ! altitudes REAL, DIMENSION(:), POINTER :: XLES_Z=>NULL() ! altitudes
...@@ -662,7 +662,7 @@ INTEGER, POINTER :: NLES_DTCOUNT=>NULL() ...@@ -662,7 +662,7 @@ INTEGER, POINTER :: NLES_DTCOUNT=>NULL()
INTEGER, POINTER :: NLES_TCOUNT=>NULL() INTEGER, POINTER :: NLES_TCOUNT=>NULL()
INTEGER, POINTER :: NSPECTRA_NI=>NULL() INTEGER, POINTER :: NSPECTRA_NI=>NULL()
INTEGER, POINTER :: NSPECTRA_NJ=>NULL() INTEGER, POINTER :: NSPECTRA_NJ=>NULL()
type(date_time), dimension(:), pointer :: xles_dates => null() type(date_time), dimension(:), pointer :: tles_dates => null()
real, dimension(:), pointer :: xles_times => null() real, dimension(:), pointer :: xles_times => null()
REAL, DIMENSION(:), POINTER :: XLES_Z=>NULL() REAL, DIMENSION(:), POINTER :: XLES_Z=>NULL()
REAL, POINTER :: XLES_ZS=>NULL() REAL, POINTER :: XLES_ZS=>NULL()
...@@ -1087,7 +1087,7 @@ SUBROUTINE LES_GOTO_MODEL(KFROM, KTO) ...@@ -1087,7 +1087,7 @@ SUBROUTINE LES_GOTO_MODEL(KFROM, KTO)
INTEGER, INTENT(IN) :: KFROM, KTO INTEGER, INTENT(IN) :: KFROM, KTO
! !
! Save current state for allocated arrays ! Save current state for allocated arrays
les_model(kfrom)%xles_dates=>xles_dates les_model(kfrom)%tles_dates=>tles_dates
les_model(kfrom)%xles_times=>xles_times les_model(kfrom)%xles_times=>xles_times
LES_MODEL(KFROM)%XLES_Z=>XLES_Z LES_MODEL(KFROM)%XLES_Z=>XLES_Z
LES_MODEL(KFROM)%XCOEFLIN_LES=>XCOEFLIN_LES LES_MODEL(KFROM)%XCOEFLIN_LES=>XCOEFLIN_LES
...@@ -1511,7 +1511,7 @@ NLES_DTCOUNT=>LES_MODEL(KTO)%NLES_DTCOUNT ...@@ -1511,7 +1511,7 @@ NLES_DTCOUNT=>LES_MODEL(KTO)%NLES_DTCOUNT
NLES_TCOUNT=>LES_MODEL(KTO)%NLES_TCOUNT NLES_TCOUNT=>LES_MODEL(KTO)%NLES_TCOUNT
NSPECTRA_NI=>LES_MODEL(KTO)%NSPECTRA_NI NSPECTRA_NI=>LES_MODEL(KTO)%NSPECTRA_NI
NSPECTRA_NJ=>LES_MODEL(KTO)%NSPECTRA_NJ NSPECTRA_NJ=>LES_MODEL(KTO)%NSPECTRA_NJ
xles_dates=>les_model(kto)%xles_dates tles_dates=>les_model(kto)%tles_dates
xles_times=>les_model(kto)%xles_times xles_times=>les_model(kto)%xles_times
XLES_Z=>LES_MODEL(KTO)%XLES_Z XLES_Z=>LES_MODEL(KTO)%XLES_Z
XLES_ZS=>LES_MODEL(KTO)%XLES_ZS XLES_ZS=>LES_MODEL(KTO)%XLES_ZS
......
...@@ -16,7 +16,7 @@ MODULE MODE_LES_DIACHRO ...@@ -16,7 +16,7 @@ MODULE MODE_LES_DIACHRO
!####################### !#######################
USE MODD_LUNIT USE MODD_LUNIT
use modd_les_n, only: xles_dates, xles_times use modd_les_n, only: tles_dates, xles_times
use mode_msg use mode_msg
...@@ -957,7 +957,7 @@ type(date_time), dimension(:), allocatable :: tzdates ...@@ -957,7 +957,7 @@ type(date_time), dimension(:), allocatable :: tzdates
Allocate( zfield(Size( pfield, 1 ), Size( pfield, 2 ), Size( pfield, 3 ), Size( pfield, 4 )) ) Allocate( zfield(Size( pfield, 1 ), Size( pfield, 2 ), Size( pfield, 3 ), Size( pfield, 4 )) )
Allocate( tzdates( nles_current_times ) ) Allocate( tzdates( nles_current_times ) )
tzdates(:) = xles_dates(:) tzdates(:) = tles_dates(:)
!Copy all fields from tpfield !Copy all fields from tpfield
tzfields(:) = tpfield tzfields(:) = tpfield
...@@ -1110,7 +1110,7 @@ type(tfield_metadata_base) :: tzfield ...@@ -1110,7 +1110,7 @@ type(tfield_metadata_base) :: tzfield
! ---------------------------------------------------------- ! ----------------------------------------------------------
allocate( tzdates( NLES_CURRENT_TIMES ) ) allocate( tzdates( NLES_CURRENT_TIMES ) )
tzdates(:) = xles_dates(:) tzdates(:) = tles_dates(:)
ikl = 1 ikl = 1
ikh = nspectra_k ikh = nspectra_k
...@@ -1234,7 +1234,7 @@ use modd_io, only: tfiledata ...@@ -1234,7 +1234,7 @@ use modd_io, only: tfiledata
use modd_les, only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, & use modd_les, only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, &
nles_current_times, nspectra_k, & nles_current_times, nspectra_k, &
xles_current_domegax, xles_current_domegay xles_current_domegax, xles_current_domegay
use modd_les_n, only: xles_dates use modd_les_n, only: tles_dates
use modd_type_date, only: date_time use modd_type_date, only: date_time
use mode_write_diachro, only: Write_diachro use mode_write_diachro, only: Write_diachro
...@@ -1260,7 +1260,7 @@ type(tfield_metadata_base) :: tzfield ...@@ -1260,7 +1260,7 @@ type(tfield_metadata_base) :: tzfield
!* 1.0 Initialization of diachro variables for LES (z,t) profiles !* 1.0 Initialization of diachro variables for LES (z,t) profiles
! ---------------------------------------------------------- ! ----------------------------------------------------------
allocate( tzdates( nles_current_times ) ) allocate( tzdates( nles_current_times ) )
tzdates(:) = xles_dates(:) tzdates(:) = tles_dates(:)
ikl = 1 ikl = 1
ikh = nspectra_k ikh = nspectra_k
......
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