source: LMDZ6/trunk/libf/dyn3dmem/geopot_loc.f90 @ 5301

Last change on this file since 5301 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • 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.6 KB
Line 
1SUBROUTINE geopot_loc ( ngrid, teta, pk, pks, phis, phi )
2  USE parallel_lmdz
3  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
4  USE paramet_mod_h
5IMPLICIT NONE
6  !=======================================================================
7  !
8  !   Auteur:  P. Le Van
9  !   -------
10  !
11  !   Objet:
12  !   ------
13  !
14  !    *******************************************************************
15  !    ....   calcul du geopotentiel aux milieux des couches    .....
16  !    *******************************************************************
17  !
18  ! ....   l'integration se fait de bas en haut  ....
19  !
20  ! .. ngrid,teta,pk,pks,phis sont des argum. d'entree pour le s-pg ..
21  !          phi               est un  argum. de sortie pour le s-pg .
22  !
23  !=======================================================================
24  !-----------------------------------------------------------------------
25
26  !   Arguments:
27  !   ----------
28  INTEGER :: ngrid
29  REAL :: teta(ijb_u:ije_u,llm),pks(ijb_u:ije_u),phis(ijb_u:ije_u), &
30        pk(ijb_u:ije_u,llm) , phi(ijb_u:ije_u,llm)
31
32
33  !   Local:
34  !   ------
35
36  INTEGER :: l, ij,ijb,ije
37
38
39  !-----------------------------------------------------------------------
40  ! calcul de phi au niveau 1 pres du sol  .....
41  ijb=ij_begin
42  ije=ij_end+iip1
43
44  IF (pole_sud)  ije=ij_end
45
46  DO  ij  = ijb, ije
47  phi( ij,1 ) = phis( ij ) + teta(ij,1) * ( pks(ij) - pk(ij,1) )
48  ENDDO
49
50  ! calcul de phi aux niveaux superieurs  .......
51
52  DO  l = 2,llm
53    DO  ij    = ijb,ije
54    phi(ij,l) = phi(ij,l-1) + 0.5 * ( teta(ij,l)  + teta(ij,l-1) ) &
55          *   (  pk(ij,l-1) -  pk(ij,l)    )
56    ENDDO
57  ENDDO
58
59  RETURN
60END SUBROUTINE geopot_loc
Note: See TracBrowser for help on using the repository browser.