Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (2 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/top_bound_loc.f90

    r5116 r5117  
    6060  !   ----------
    6161
    62   real,intent(inout) :: ucov(iip1,jjb_u:jje_u,llm) ! covariant zonal wind
    63   real,intent(inout) :: vcov(iip1,jjb_v:jje_v,llm) ! covariant meridional wind
    64   real,intent(inout) :: teta(iip1,jjb_u:jje_u,llm) ! potential temperature
    65   real,intent(in) :: masse(iip1,jjb_u:jje_u,llm) ! mass of atmosphere
    66   real,intent(in) :: dt ! time step (s) of sponge model
     62  REAL,INTENT(INOUT) :: ucov(iip1,jjb_u:jje_u,llm) ! covariant zonal wind
     63  REAL,INTENT(INOUT) :: vcov(iip1,jjb_v:jje_v,llm) ! covariant meridional wind
     64  REAL,INTENT(INOUT) :: teta(iip1,jjb_u:jje_u,llm) ! potential temperature
     65  REAL,INTENT(IN) :: masse(iip1,jjb_u:jje_u,llm) ! mass of atmosphere
     66  REAL,INTENT(IN) :: dt ! time step (s) of sponge model
    6767
    6868   ! REAL dv(iip1,jjb_v:jje_v,llm),du(iip1,jjb_u:jje_u,llm)
     
    7878  INTEGER :: i
    7979  REAL,SAVE :: rdamp(llm)
    80   real,save :: lambda(llm) ! inverse or quenching time scale (Hz)
     80  REAL,save :: lambda(llm) ! inverse or quenching time scale (Hz)
    8181  LOGICAL,SAVE :: first=.TRUE.
    8282  INTEGER :: j,l,jjb,jje
    8383
    8484
    85   if (iflag_top_bound == 0) return
    86 
    87   if (first) THEN
     85  IF (iflag_top_bound == 0) return
     86
     87  IF (first) THEN
    8888!$OMP BARRIER
    8989!$OMP MASTER
    90      if (iflag_top_bound == 1) THEN
     90     IF (iflag_top_bound == 1) THEN
    9191  ! sponge quenching over the topmost 4 atmospheric layers
    9292         lambda(:)=0.
     
    9595         lambda(llm-2)=tau_top_bound/4.
    9696         lambda(llm-3)=tau_top_bound/8.
    97      else if (iflag_top_bound == 2) THEN
     97     ELSE IF (iflag_top_bound == 2) THEN
    9898  ! sponge quenching over topmost layers down to pressures which are
    9999  ! higher than 100 times the topmost layer pressure
     
    110110     WRITE(lunout,*)'p (Pa)  z(km)  tau(s)   1./tau (Hz)'
    111111     do l=1,llm
    112        if (rdamp(l)/=0.) THEN
     112       IF (rdamp(l)/=0.) THEN
    113113         WRITE(lunout,'(6(1pe12.4,1x))') &
    114114               presnivs(l),log(preff/presnivs(l))*scaleheight, &
     
    119119!$OMP END MASTER
    120120!$OMP BARRIER
    121   endif ! of if (first)
     121  ENDIF ! of if (first)
    122122
    123123
     
    125125
    126126  ! compute zonal average of vcov (or set it to zero)
    127   if (mode_top_bound>=2) THEN
     127  IF (mode_top_bound>=2) THEN
    128128   jjb=jj_begin
    129129   jje=jj_end
     
    150150   enddo
    151151!$OMP END DO NOWAIT
    152   endif ! of if (mode_top_bound.ge.2)
     152  ENDIF ! of if (mode_top_bound.ge.2)
    153153
    154154  ! compute zonal average of u (or set it to zero)
    155   if (mode_top_bound>=2) THEN
     155  IF (mode_top_bound>=2) THEN
    156156   jjb=jj_begin
    157157   jje=jj_end
     
    177177   enddo
    178178!$OMP END DO NOWAIT
    179   endif ! of if (mode_top_bound.ge.2)
     179  ENDIF ! of if (mode_top_bound.ge.2)
    180180
    181181  ! compute zonal average of potential temperature, if necessary
    182   if (mode_top_bound>=3) THEN
     182  IF (mode_top_bound>=3) THEN
    183183   jjb=jj_begin
    184184   jje=jj_end
     
    198198   enddo
    199199!$OMP END DO NOWAIT
    200   endif ! of if (mode_top_bound.ge.3)
    201 
    202   if (mode_top_bound>=1) THEN
     200  ENDIF ! of if (mode_top_bound.ge.3)
     201
     202  IF (mode_top_bound>=1) THEN
    203203   ! Apply sponge quenching on vcov:
    204204   jjb=jj_begin
     
    233233   enddo
    234234!$OMP END DO NOWAIT
    235   endif ! of if (mode_top_bound.ge.1)
    236 
    237   if (mode_top_bound>=3) THEN
     235  ENDIF ! of if (mode_top_bound.ge.1)
     236
     237  IF (mode_top_bound>=3) THEN
    238238   ! Apply sponge quenching on teta:
    239239   jjb=jj_begin
     
    252252   enddo
    253253!$OMP END DO NOWAIT
    254   endif ! of if (mode_top_bond.ge.3)
     254  ENDIF ! of if (mode_top_bond.ge.3)
    255255
    256256END SUBROUTINE top_bound_loc
Note: See TracChangeset for help on using the changeset viewer.