source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/massdair_loc.f90 @ 5209

Last change on this file since 5209 was 5159, checked in by abarral, 7 weeks ago

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