Changeset 5159 for LMDZ6/branches/Amaury_dev/libf/dyn3dmem/massdair_loc.f90
- Timestamp:
- Aug 2, 2024, 9:58:25 PM (3 months ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/massdair_loc.f90
r5136 r5159 3 3 USE lmdz_comgeom 4 4 5 ! 5 6 6 ! ********************************************************************* 7 7 ! .... Calcule la masse d'air dans chaque maille .... 8 8 ! ********************************************************************* 9 ! 9 10 10 ! Auteurs : P. Le Van , Fr. Hourdin . 11 11 ! .......... 12 ! 12 13 13 ! .. p est un argum. d'entree pour le s-pg ... 14 14 ! .. masse est un argum.de sortie pour le s-pg ... 15 ! 15 16 16 ! .... p est defini aux interfaces des llm couches ..... 17 ! 17 18 USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm 19 USE lmdz_paramet 18 20 IMPLICIT NONE 19 21 ! 20 INCLUDE "dimensions.h" 21 INCLUDE "paramet.h" 22 ! 22 23 24 23 25 ! ..... arguments .... 24 ! 26 25 27 REAL :: p(ijb_u:ije_u,llmp1), masse(ijb_u:ije_u,llm) 26 28 … … 31 33 REAL :: massemoyn, massemoys 32 34 33 ! 34 ! 35 36 35 37 ! Methode pour calculer massebx et masseby . 36 38 ! ---------------------------------------- 37 ! 39 38 40 ! A chaque point scalaire P (i,j) est affecte 4 coefficients d'aires 39 41 ! alpha1(i,j) calcule au point ( i+1/4,j-1/4 ) … … 41 43 ! alpha3(i,j) calcule au point ( i-1/4,j+1/4 ) 42 44 ! alpha4(i,j) calcule au point ( i-1/4,j-1/4 ) 43 ! 45 44 46 ! Avec alpha1(i,j) = aire(i+1/4,j-1/4)/ aire(i,j) 45 ! 47 46 48 ! N.B . Pour plus de details, voir s-pg ... iniconst ... 47 ! 48 ! 49 ! 49 50 51 50 52 ! alpha4 . . alpha1 . alpha4 51 53 ! (i,j) (i,j) (i+1,j) 52 ! 54 53 55 ! P . U . . P 54 56 ! (i,j) (i,j) (i+1,j) 55 ! 57 56 58 ! alpha3 . . alpha2 .alpha3 57 59 ! (i,j) (i,j) (i+1,j) 58 ! 60 59 61 ! V . Z . . V 60 62 ! (i,j) 61 ! 63 62 64 ! alpha4 . . alpha1 .alpha4 63 65 ! (i,j+1) (i,j+1) (i+1,j+1) 64 ! 66 65 67 ! P . U . . P 66 68 ! (i,j+1) (i+1,j+1) 67 ! 68 ! 69 ! 69 70 71 70 72 ! On a : 71 ! 73 72 74 ! massebx(i,j) = masse(i ,j) * ( alpha1(i ,j) + alpha2(i,j)) + 73 75 ! masse(i+1,j) * ( alpha3(i+1,j) + alpha4(i+1,j) ) 74 76 ! localise au point ... U (i,j) ... 75 ! 77 76 78 ! masseby(i,j) = masse(i,j ) * ( alpha2(i,j ) + alpha3(i,j ) + 77 79 ! masse(i,j+1) * ( alpha1(i,j+1) + alpha4(i,j+1) 78 80 ! localise au point ... V (i,j) ... 79 ! 80 ! 81 82 81 83 !======================================================================= 82 84 … … 92 94 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 93 95 DO l = 1 , llm 94 ! 96 95 97 DO ij = ijb, ije 96 98 masse(ij,l) = airesurg(ij) * ( p(ij,l) - p(ij,l+1) ) 97 99 ENDDO 98 ! 100 99 101 DO ij = ijb, ije,iip1 100 102 masse(ij+ iim,l) = masse(ij,l) 101 103 ENDDO 102 ! 104 103 105 ! DO ij = 1, iim 104 106 ! masse( ij ,l) = masse( ij ,l) * aire( ij )
Note: See TracChangeset
for help on using the changeset viewer.