source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/massdair.f90 @ 5105

Last change on this file since 5105 was 5105, checked in by abarral, 8 weeks 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.0 KB
Line 
1
2! $Header$
3
4SUBROUTINE massdair( p, masse )
5  !
6  ! *********************************************************************
7  !   ....  Calcule la masse d'air  dans chaque maille   ....
8  ! *********************************************************************
9  !
10  !    Auteurs : P. Le Van , Fr. Hourdin  .
11  !   ..........
12  !
13  !  ..    p                      est  un argum. d'entree pour le s-pg ...
14  !  ..  masse                    est un  argum.de sortie pour le s-pg ...
15  !
16  !  ....  p est defini aux interfaces des llm couches   .....
17  !
18  IMPLICIT NONE
19  !
20  include "dimensions.h"
21  include "paramet.h"
22  include "comgeom.h"
23  !
24  !  .....   arguments  ....
25  !
26  REAL :: p(ip1jmp1,llmp1), masse(ip1jmp1,llm)
27
28  !   ....  Variables locales  .....
29
30  INTEGER :: l,ij
31  REAL :: massemoyn, massemoys
32
33  REAL :: SSUM
34  !
35  !
36  !   Methode pour calculer massebx et masseby .
37  !   ----------------------------------------
38  !
39  !    A chaque point scalaire P (i,j) est affecte 4 coefficients d'aires
40  !   alpha1(i,j)  calcule  au point ( i+1/4,j-1/4 )
41  !   alpha2(i,j)  calcule  au point ( i+1/4,j+1/4 )
42  !   alpha3(i,j)  calcule  au point ( i-1/4,j+1/4 )
43  !   alpha4(i,j)  calcule  au point ( i-1/4,j-1/4 )
44  !
45  !    Avec  alpha1(i,j) = aire(i+1/4,j-1/4)/ aire(i,j)
46  !
47  !    N.B .  Pour plus de details, voir s-pg  ...  iniconst ...
48  !
49  !
50  !
51  !   alpha4 .         . alpha1    . alpha4
52  !    (i,j)             (i,j)       (i+1,j)
53  !
54  !         P .        U .          . P
55  !       (i,j)       (i,j)         (i+1,j)
56  !
57  !   alpha3 .         . alpha2    .alpha3
58  !    (i,j)              (i,j)     (i+1,j)
59  !
60  !         V .        Z .          . V
61  !       (i,j)
62  !
63  !   alpha4 .         . alpha1    .alpha4
64  !   (i,j+1)            (i,j+1)   (i+1,j+1)
65  !
66  !         P .        U .          . P
67  !      (i,j+1)                    (i+1,j+1)
68  !
69  !
70  !
71  !                   On  a :
72  !
73  !    massebx(i,j) = masse(i  ,j) * ( alpha1(i  ,j) + alpha2(i,j))   +
74  !               masse(i+1,j) * ( alpha3(i+1,j) + alpha4(i+1,j) )
75  ! localise  au point  ... U (i,j) ...
76  !
77  !    masseby(i,j) = masse(i,j  ) * ( alpha2(i,j  ) + alpha3(i,j  )  +
78  !               masse(i,j+1) * ( alpha1(i,j+1) + alpha4(i,j+1)
79  ! localise  au point  ... V (i,j) ...
80  !
81  !
82  !=======================================================================
83
84  DO   l = 1 , llm
85  !
86    DO    ij     = 1, ip1jmp1
87     masse(ij,l) = airesurg(ij) * ( p(ij,l) - p(ij,l+1) )
88    ENDDO
89  !
90    DO   ij = 1, ip1jmp1,iip1
91     masse(ij+ iim,l) = masse(ij,l)
92    ENDDO
93  !
94  !   DO    ij     = 1,  iim
95  !    masse(   ij   ,l) = masse(   ij   ,l) * aire(  ij    )
96  !    masse(ij+ip1jm,l) = masse(ij+ip1jm,l) * aire(ij+ip1jm)
97  !   ENDDO
98  !    massemoyn         = SSUM(iim,masse(   1   ,l),1)/ apoln
99  !    massemoys         = SSUM(iim,masse(ip1jm+1,l),1)/ apols
100  !   DO    ij     = 1, iip1
101  !    masse(   ij   ,l )    = massemoyn
102  !    masse(ij+ip1jm,l )    = massemoys
103  !   ENDDO
104
105  END DO
106  !
107  RETURN
108END SUBROUTINE massdair
Note: See TracBrowser for help on using the repository browser.