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