Ignore:
Timestamp:
Oct 21, 2024, 2:58:45 PM (23 hours ago)
Author:
abarral
Message:

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3dmem/pression_loc.f90

    r5245 r5246  
    1       SUBROUTINE pression_loc( ngrid, ap, bp, ps, p )
    2       USE parallel_lmdz, ONLY: ij_begin, ij_end, ijb_u, ije_u,
    3      &                         pole_nord, pole_sud, omp_chunk
    4 c
     1SUBROUTINE pression_loc( ngrid, ap, bp, ps, p )
     2  USE parallel_lmdz, ONLY: ij_begin, ij_end, ijb_u, ije_u, &
     3        pole_nord, pole_sud, omp_chunk
     4  !
    55
    6 c      Auteurs : P. Le Van , Fr.Hourdin  .
     6  !  Auteurs : P. Le Van , Fr.Hourdin  .
    77
    8 c  ************************************************************************
    9 c     Calcule la pression p(l) aux differents niveaux l = 1 ( niveau du
    10 c     sol) a l = llm +1 ,ces niveaux correspondant aux interfaces des (llm)
    11 c     couches , avec  p(ij,llm +1) = 0.  et p(ij,1) = ps(ij)  .     
    12 c  ************************************************************************
    13 c
    14       IMPLICIT NONE
    15 c
    16       INCLUDE "dimensions.h"
    17       INCLUDE "paramet.h"
    18 c
    19       INTEGER,INTENT(IN) :: ngrid ! not used
    20       INTEGER l,ij
    21  
    22       REAL,INTENT(IN) :: ap( llmp1 ), bp( llmp1 ), ps( ijb_u:ije_u )
    23       REAL,INTENT(OUT) :: p( ijb_u:ije_u,llmp1 )
    24      
    25       INTEGER ijb,ije
     8  !  ************************************************************************
     9  ! Calcule la pression p(l) aux differents niveaux l = 1 ( niveau du
     10  ! sol) a l = llm +1 ,ces niveaux correspondant aux interfaces des (llm)
     11  ! couches , avec  p(ij,llm +1) = 0.  et p(ij,1) = ps(ij)  .
     12  !  ************************************************************************
     13  !
     14  IMPLICIT NONE
     15  !
     16  INCLUDE "dimensions.h"
     17  INCLUDE "paramet.h"
     18  !
     19  INTEGER,INTENT(IN) :: ngrid ! not used
     20  INTEGER :: l,ij
    2621
    27      
    28       ijb=ij_begin-iip1
    29       ije=ij_end+2*iip1
    30      
    31       if (pole_nord) ijb=ij_begin
    32       if (pole_sud)  ije=ij_end
     22  REAL,INTENT(IN) :: ap( llmp1 ), bp( llmp1 ), ps( ijb_u:ije_u )
     23  REAL,INTENT(OUT) :: p( ijb_u:ije_u,llmp1 )
    3324
    34 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    35       DO    l    = 1, llmp1
    36         DO  ij   = ijb, ije
    37          p(ij,l) = ap(l) + bp(l) * ps(ij)
    38         ENDDO
    39       ENDDO
    40 c$OMP END DO NOWAIT   
    41       RETURN
    42       END
     25  INTEGER :: ijb,ije
     26
     27
     28  ijb=ij_begin-iip1
     29  ije=ij_end+2*iip1
     30
     31  if (pole_nord) ijb=ij_begin
     32  if (pole_sud)  ije=ij_end
     33
     34!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     35  DO    l    = 1, llmp1
     36    DO  ij   = ijb, ije
     37     p(ij,l) = ap(l) + bp(l) * ps(ij)
     38    ENDDO
     39  ENDDO
     40!$OMP END DO NOWAIT
     41  RETURN
     42END SUBROUTINE pression_loc
Note: See TracChangeset for help on using the changeset viewer.