source: LMDZ6/trunk/libf/dyn3dmem/pression_loc.f90 @ 5272

Last change on this file since 5272 was 5272, checked in by abarral, 3 months ago

Turn paramet.h into a module

  • 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.2 KB
RevLine 
[5246]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  !
[1632]5
[5246]6  !  Auteurs : P. Le Van , Fr.Hourdin  .
[1632]7
[5246]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  !
[5271]14  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5272]15USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
16          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
[5271]17IMPLICIT NONE
[5246]18  !
[5271]19
[5272]20
[5246]21  !
22  INTEGER,INTENT(IN) :: ngrid ! not used
23  INTEGER :: l,ij
[1632]24
[5246]25  REAL,INTENT(IN) :: ap( llmp1 ), bp( llmp1 ), ps( ijb_u:ije_u )
26  REAL,INTENT(OUT) :: p( ijb_u:ije_u,llmp1 )
[1632]27
[5246]28  INTEGER :: ijb,ije
29
30
31  ijb=ij_begin-iip1
32  ije=ij_end+2*iip1
33
34  if (pole_nord) ijb=ij_begin
35  if (pole_sud)  ije=ij_end
36
37!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
38  DO    l    = 1, llmp1
39    DO  ij   = ijb, ije
40     p(ij,l) = ap(l) + bp(l) * ps(ij)
41    ENDDO
42  ENDDO
43!$OMP END DO NOWAIT
44  RETURN
45END SUBROUTINE pression_loc
Note: See TracBrowser for help on using the repository browser.