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

Last change on this file since 5272 was 5272, checked in by abarral, 27 hours 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: 3.3 KB
RevLine 
[5246]1SUBROUTINE massdair_loc( p, masse )
2  USE parallel_lmdz
3  !
4  ! *********************************************************************
5  !   ....  Calcule la masse d'air  dans chaque maille   ....
6  ! *********************************************************************
7  !
8  !    Auteurs : P. Le Van , Fr. Hourdin  .
9  !   ..........
10  !
11  !  ..    p                      est  un argum. d'entree pour le s-pg ...
12  !  ..  masse                    est un  argum.de sortie pour le s-pg ...
13  !
14  !  ....  p est defini aux interfaces des llm couches   .....
15  !
[5271]16  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5272]17USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
18          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
[5271]19IMPLICIT NONE
[5246]20  !
[5271]21
[5272]22
[5246]23  include "comgeom.h"
24  !
25  !  .....   arguments  ....
26  !
27  REAL :: p(ijb_u:ije_u,llmp1), masse(ijb_u:ije_u,llm)
[1632]28
[5246]29  !   ....  Variables locales  .....
[1632]30
[5246]31  INTEGER :: l,ij
32  INTEGER :: ijb,ije
33  REAL :: massemoyn, massemoys
[1632]34
[5246]35  REAL :: SSUM
36  EXTERNAL SSUM
37  !
38  !
39  !   Methode pour calculer massebx et masseby .
40  !   ----------------------------------------
41  !
42  !    A chaque point scalaire P (i,j) est affecte 4 coefficients d'aires
43  !   alpha1(i,j)  calcule  au point ( i+1/4,j-1/4 )
44  !   alpha2(i,j)  calcule  au point ( i+1/4,j+1/4 )
45  !   alpha3(i,j)  calcule  au point ( i-1/4,j+1/4 )
46  !   alpha4(i,j)  calcule  au point ( i-1/4,j-1/4 )
47  !
48  !    Avec  alpha1(i,j) = aire(i+1/4,j-1/4)/ aire(i,j)
49  !
50  !    N.B .  Pour plus de details, voir s-pg  ...  iniconst ...
51  !
52  !
53  !
54  !   alpha4 .         . alpha1    . alpha4
55  !    (i,j)             (i,j)       (i+1,j)
56  !
57  !         P .        U .          . P
58  !       (i,j)       (i,j)         (i+1,j)
59  !
60  !   alpha3 .         . alpha2    .alpha3
61  !    (i,j)              (i,j)     (i+1,j)
62  !
63  !         V .        Z .          . V
64  !       (i,j)
65  !
66  !   alpha4 .         . alpha1    .alpha4
67  !   (i,j+1)            (i,j+1)   (i+1,j+1)
68  !
69  !         P .        U .          . P
70  !      (i,j+1)                    (i+1,j+1)
71  !
72  !
73  !
74  !                   On  a :
75  !
76  !    massebx(i,j) = masse(i  ,j) * ( alpha1(i  ,j) + alpha2(i,j))   +
77  !               masse(i+1,j) * ( alpha3(i+1,j) + alpha4(i+1,j) )
78  ! localise  au point  ... U (i,j) ...
79  !
80  !    masseby(i,j) = masse(i,j  ) * ( alpha2(i,j  ) + alpha3(i,j  )  +
81  !               masse(i,j+1) * ( alpha1(i,j+1) + alpha4(i,j+1)
82  ! localise  au point  ... V (i,j) ...
83  !
84  !
85  !=======================================================================
[1632]86
87
88
[5246]89
90  ijb=ij_begin-iip1
91  ije=ij_end+2*iip1
92
93  if (pole_nord) ijb=ij_begin
94  if (pole_sud)  ije=ij_end
95
96!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
97  DO    l = 1 , llm
98  !
99    DO    ij     = ijb, ije
100     masse(ij,l) = airesurg(ij) * ( p(ij,l) - p(ij,l+1) )
101    ENDDO
102  !
103    DO   ij = ijb, ije,iip1
104     masse(ij+ iim,l) = masse(ij,l)
105    ENDDO
106  !
107  !   DO    ij     = 1,  iim
108  !    masse(   ij   ,l) = masse(   ij   ,l) * aire(  ij    )
109  !    masse(ij+ip1jm,l) = masse(ij+ip1jm,l) * aire(ij+ip1jm)
110  !   ENDDO
111  !    massemoyn         = SSUM(iim,masse(   1   ,l),1)/ apoln
112  !    massemoys         = SSUM(iim,masse(ip1jm+1,l),1)/ apols
113  !   DO    ij     = 1, iip1
114  !    masse(   ij   ,l )    = massemoyn
115  !    masse(ij+ip1jm,l )    = massemoys
116  !   ENDDO
117
118  END DO
119!$OMP END DO NOWAIT
120  !
121  RETURN
122END SUBROUTINE massdair_loc
Note: See TracBrowser for help on using the repository browser.