Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (4 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/integrd_loc.f90

    r5116 r5117  
    99  USE lmdz_filtreg_p
    1010  USE write_field_loc
    11   USE write_field
     11  USE lmdz_write_field
    1212  USE integrd_mod
    1313  USE comconst_mod, ONLY: pi
     
    1515  USE comvert_mod, ONLY: ap, bp
    1616  USE temps_mod, ONLY: dt
    17   USE strings_mod, ONLY: int2str
     17  USE lmdz_strings, ONLY: int2str
    1818
    1919  IMPLICIT NONE
     
    4343  !   ----------
    4444
    45   INTEGER,intent(in) :: nq ! number of tracers to handle in this routine
     45  INTEGER,INTENT(IN) :: nq ! number of tracers to handle in this routine
    4646
    4747  REAL,INTENT(INOUT) :: vcov(ijb_v:ije_v,llm) ! covariant meridional wind
     
    9090
    9191!$OMP BARRIER
    92   if (pole_nord) THEN
     92  IF (pole_nord) THEN
    9393!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    9494    DO  l = 1,llm
     
    101101  ENDIF
    102102
    103   if (pole_sud) THEN
     103  IF (pole_sud) THEN
    104104!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    105105    DO  l = 1,llm
     
    195195  !   !WRITE(*,*) 'integrd 200'
    196196!$OMP MASTER
    197   if (pole_nord) THEN
     197  IF (pole_nord) THEN
    198198
    199199    DO  ij    = 1, iim
     
    207207  ENDIF
    208208
    209   if (pole_sud) THEN
     209  IF (pole_sud) THEN
    210210
    211211    DO  ij    = 1, iim
     
    255255  ijb=ij_begin
    256256  ije=ij_end
    257   if (pole_nord) ijb=ij_begin+iip1
    258   if (pole_sud)  ije=ij_end-iip1
     257  IF (pole_nord) ijb=ij_begin+iip1
     258  IF (pole_sud)  ije=ij_end-iip1
    259259
    260260  DO ij = ijb,ije
     
    265265  ijb=ij_begin
    266266  ije=ij_end
    267   if (pole_sud)  ije=ij_end-iip1
     267  IF (pole_sud)  ije=ij_end-iip1
    268268
    269269  DO ij = ijb,ije
     
    320320    ucovm1(ijb:ije,l)=uscr(ijb:ije)
    321321    tetam1(ijb:ije,l)=hscr(ijb:ije)
    322     if (pole_sud) ije=ij_end-iip1
     322    IF (pole_sud) ije=ij_end-iip1
    323323    vcovm1(ijb:ije,l)=vscr(ijb:ije)
    324324
     
    334334  ije=ij_end
    335335
    336      if (planet_type=="earth") THEN
     336     IF (planet_type=="earth") THEN
    337337  ! Earth-specific treatment of first 2 tracers (water)
    338338!$OMP BARRIER
     
    415415  !c$OMP END DO NOWAIT
    416416
    417   endif ! of if (planet_type.eq."earth")
     417  ENDIF ! of if (planet_type.EQ."earth")
    418418
    419419  !
Note: See TracChangeset for help on using the changeset viewer.