source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/pression_loc.f90 @ 5116

Last change on this file since 5116 was 5105, checked in by abarral, 2 months ago

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 1.1 KB
Line 
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  !
5
6  !  Auteurs : P. Le Van , Fr.Hourdin  .
7
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
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
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
42END SUBROUTINE pression_loc
Note: See TracBrowser for help on using the repository browser.