/[lmdze]/trunk/dyn3d/interpre.f
ViewVC logotype

Contents of /trunk/dyn3d/interpre.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 81 - (show annotations)
Wed Mar 5 14:38:41 2014 UTC (10 years, 2 months ago) by guez
Original Path: trunk/dyn3d/interpre.f90
File size: 3097 byte(s)
 Converted to free source form files which were still in fixed source
form. The conversion was done using the polish mode of the NAG Fortran
Compiler.

In addition to converting to free source form, the processing of the
files also:

-- indented the code (including comments);

-- set Fortran keywords to uppercase, and set all other identifiers
to lower case;

-- added qualifiers to end statements (for example "end subroutine
conflx", instead of "end");

-- changed the terminating statements of all DO loops so that each
loop ends with an ENDDO statement (instead of a labeled continue).

1
2 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/interpre.F,v 1.1.1.1 2004/05/19
3 ! 12:53:07 lmdzadmin Exp $
4
5 SUBROUTINE interpre(q, qppm, w, fluxwppm, masse, apppm, bpppm, massebx, &
6 masseby, pbaru, pbarv, unatppm, vnatppm, psppm)
7
8 USE dimens_m
9 USE paramet_m
10 USE comconst
11 USE disvert_m
12 USE conf_gcm_m
13 USE conf_gcm_m
14 USE comgeom
15 USE temps
16 USE ener
17 IMPLICIT NONE
18
19 ! ---------------------------------------------------
20 ! Arguments
21 REAL apppm(llm+1), bpppm(llm+1)
22 REAL q(iip1, jjp1, llm), qppm(iim, jjp1, llm)
23 ! ---------------------------------------------------
24 REAL masse(iip1, jjp1, llm)
25 REAL massebx(iip1, jjp1, llm), masseby(iip1, jjm, llm)
26 REAL w(iip1, jjp1, llm+1)
27 REAL fluxwppm(iim, jjp1, llm)
28 REAL, INTENT (IN) :: pbaru(iip1, jjp1, llm)
29 REAL, INTENT (IN) :: pbarv(iip1, jjm, llm)
30 REAL unatppm(iim, jjp1, llm)
31 REAL vnatppm(iim, jjp1, llm)
32 REAL psppm(iim, jjp1)
33 ! ---------------------------------------------------
34 ! Local
35 REAL vnat(iip1, jjp1, llm)
36 REAL unat(iip1, jjp1, llm)
37 REAL fluxw(iip1, jjp1, llm)
38 REAL smass(iip1, jjp1)
39 ! ----------------------------------------------------
40 INTEGER l, ij, i, j
41
42 ! CALCUL DE LA PRESSION DE SURFACE
43 ! Les coefficients ap et bp sont passés en common
44 ! Calcul de la pression au sol en mb optimisée pour
45 ! la vectorialisation
46
47 DO j = 1, jjp1
48 DO i = 1, iip1
49 smass(i, j) = 0.
50 END DO
51 END DO
52
53 DO l = 1, llm
54 DO j = 1, jjp1
55 DO i = 1, iip1
56 smass(i, j) = smass(i, j) + masse(i, j, l)
57 END DO
58 END DO
59 END DO
60
61 DO j = 1, jjp1
62 DO i = 1, iim
63 psppm(i, j) = smass(i, j)/aire_2d(i, j)*g*0.01
64 END DO
65 END DO
66
67 ! RECONSTRUCTION DES CHAMPS CONTRAVARIANTS
68 ! Le programme ppm3d travaille avec les composantes
69 ! de vitesse et pas les flux, on doit donc passer de l'un à l'autre
70 ! Dans le même temps, on fait le changement d'orientation du vent en v
71 DO l = 1, llm
72 DO j = 1, jjm
73 DO i = 1, iip1
74 vnat(i, j, l) = -pbarv(i, j, l)/masseby(i, j, l)*cv_2d(i, j)
75 END DO
76 END DO
77 DO i = 1, iim
78 vnat(i, jjp1, l) = 0.
79 END DO
80 DO j = 1, jjp1
81 DO i = 1, iip1
82 unat(i, j, l) = pbaru(i, j, l)/massebx(i, j, l)*cu_2d(i, j)
83 END DO
84 END DO
85 END DO
86
87 ! CALCUL DU FLUX MASSIQUE VERTICAL
88 ! Flux en l=1 (sol) nul
89 fluxw = 0.
90 DO l = 1, llm
91 DO j = 1, jjp1
92 DO i = 1, iip1
93 fluxw(i, j, l) = w(i, j, l)*g*0.01/aire_2d(i, j)
94 END DO
95 END DO
96 END DO
97
98 ! INVERSION DES NIVEAUX
99 ! le programme ppm3d travaille avec une 3ème coordonnée inversée par
100 ! rapport
101 ! de celle du LMDZ: z=1<=>niveau max, z=llm+1<=>surface
102 ! On passe donc des niveaux du LMDZ à ceux de Lin
103
104 DO l = 1, llm + 1
105 apppm(l) = ap(llm+2-l)
106 bpppm(l) = bp(llm+2-l)
107 END DO
108
109 DO l = 1, llm
110 DO j = 1, jjp1
111 DO i = 1, iim
112 unatppm(i, j, l) = unat(i, j, llm-l+1)
113 vnatppm(i, j, l) = vnat(i, j, llm-l+1)
114 fluxwppm(i, j, l) = fluxw(i, j, llm-l+1)
115 qppm(i, j, l) = q(i, j, llm-l+1)
116 END DO
117 END DO
118 END DO
119
120 RETURN
121 END SUBROUTINE interpre
122
123
124
125
126
127

  ViewVC Help
Powered by ViewVC 1.1.21