/[lmdze]/trunk/libf/dyn3d/sortvarc0.f90
ViewVC logotype

Annotation of /trunk/libf/dyn3d/sortvarc0.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 23 - (hide annotations)
Mon Dec 14 15:25:16 2009 UTC (14 years, 5 months ago) by guez
File size: 3021 byte(s)
Split "orografi.f": one file for each procedure. Put the created files
in new directory "Orography".

Removed argument "vcov" of procedure "sortvarc". Removed arguments
"itau" and "time" of procedure "caldyn0". Removed arguments "itau",
"time" and "vcov" of procedure "sortvarc0".

Removed argument "time" of procedure "dynredem1". Removed NetCDF
variable "temps" in files "start.nc" and "restart.nc", because its
value is always 0.

Removed argument "nq" of procedures "iniadvtrac" and "leapfrog". The
number of "tracers read in "traceur.def" must now be equal to "nqmx",
or "nqmx" must equal 4 if there is no file "traceur.def". Replaced
variable "nq" by constant "nqmx" in "leapfrog".

NetCDF variable for ozone field in "coefoz.nc" must now be called
"tro3" instead of "r".

Fixed bug in "zenang".

1 guez 23 SUBROUTINE sortvarc0(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp)
2 guez 3
3 guez 23 ! From dyn3d/sortvarc0.F, v 1.1.1.1 2004/05/19 12:53:07
4     ! Auteur : P. Le Van
5     ! Objet : sortie des variables de contrĂ´le
6 guez 3
7 guez 23 USE dimens_m, ONLY : iim, jjm, llm
8     USE paramet_m, ONLY : iip1, iip2, ijp1llm, ip1jm, ip1jmp1, jjp1
9     USE comconst, ONLY : daysec, g, omeg, rad
10     USE comgeom, ONLY : aire, cu, rlatu
11     USE ener, ONLY : ang0, etot0, ptot0, rmsdpdt, rmsv, stot0, ztot0
12 guez 3
13 guez 23 IMPLICIT NONE
14 guez 3
15 guez 23 ! Arguments:
16 guez 3
17 guez 23 REAL, INTENT (IN) :: ucov(ip1jmp1, llm)
18     REAL :: teta(ip1jmp1, llm), masse(ip1jmp1, llm)
19     REAL, INTENT (IN) :: ps(ip1jmp1)
20     REAL, INTENT (IN) :: phis(ip1jmp1)
21     REAL :: vorpot(ip1jm, llm)
22     REAL :: phi(ip1jmp1, llm), bern(ip1jmp1, llm)
23     REAL :: dp(ip1jmp1)
24     REAL, INTENT (IN) :: pk(ip1jmp1, llm)
25 guez 3
26 guez 23 ! Local:
27 guez 3
28 guez 23 REAL :: vor(ip1jm), bernf(ip1jmp1, llm), ztotl(llm)
29     REAL :: etotl(llm), stotl(llm), rmsvl(llm), angl(llm), ge(ip1jmp1)
30     REAL :: cosphi(ip1jm), omegcosp(ip1jm)
31     REAL radomeg
32     REAL massebxy(ip1jm, llm)
33     INTEGER l, ij
34 guez 3
35 guez 23 REAL :: ssum
36 guez 3
37 guez 23 !-----------------------------------------------------------------------
38 guez 3
39 guez 23 PRINT *, 'Call sequence information: sortvarc0'
40 guez 3
41 guez 23 CALL massbarxy(masse, massebxy)
42 guez 3
43 guez 23 ! Calcul de rmsdpdt
44     ge = dp*dp
45     rmsdpdt = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
46     rmsdpdt = daysec*1.E-2*sqrt(rmsdpdt / (iim * jjp1))
47     CALL scopy(ijp1llm, bern, 1, bernf, 1)
48     CALL filtreg(bernf, jjp1, llm, -2, 2, .TRUE., 1)
49 guez 3
50 guez 23 ! Calcul du moment angulaire
51 guez 3
52 guez 23 radomeg = rad * omeg
53 guez 3
54 guez 23 DO ij = iip2, ip1jm
55     cosphi(ij) = cos(rlatu((ij-1)/iip1+1))
56     omegcosp(ij) = radomeg*cosphi(ij)
57     END DO
58 guez 3
59 guez 23 ! Calcul de l'energie, de l'enstrophie, de l'entropie et de rmsv
60 guez 3
61 guez 23 DO l = 1, llm
62     DO ij = 1, ip1jm
63     vor(ij) = vorpot(ij, l)*vorpot(ij, l)*massebxy(ij, l)
64     END DO
65     ztotl(l) = (ssum(ip1jm, vor, 1)-ssum(jjm, vor, iip1))
66 guez 3
67 guez 23 DO ij = 1, ip1jmp1
68     ge(ij) = masse(ij, l) &
69     *(phis(ij)+teta(ij, l)*pk(ij, l)+bernf(ij, l)-phi(ij, l))
70     END DO
71     etotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
72 guez 3
73 guez 23 DO ij = 1, ip1jmp1
74     ge(ij) = masse(ij, l)*teta(ij, l)
75     END DO
76     stotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
77 guez 3
78 guez 23 DO ij = 1, ip1jmp1
79     ge(ij) = masse(ij, l)*amax1(bernf(ij, l)-phi(ij, l), 0.)
80     END DO
81     rmsvl(l) = 2.*(ssum(ip1jmp1, ge, 1)-ssum(jjp1, ge, iip1))
82 guez 3
83 guez 23 DO ij = iip2, ip1jm
84     ge(ij) = (ucov(ij, l)/cu(ij)+omegcosp(ij))*masse(ij, l)*cosphi(ij)
85     END DO
86     angl(l) = rad / g &
87     * (ssum(ip1jm-iip1, ge(iip2), 1)-ssum(jjm-1, ge(iip2), iip1))
88     END DO
89 guez 3
90 guez 23 DO ij = 1, ip1jmp1
91     ge(ij) = ps(ij)*aire(ij)
92     END DO
93     ptot0 = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
94     etot0 = ssum(llm, etotl, 1)
95     ztot0 = ssum(llm, ztotl, 1)
96     stot0 = ssum(llm, stotl, 1)
97     rmsv = ssum(llm, rmsvl, 1)
98     ang0 = ssum(llm, angl, 1)
99 guez 3
100 guez 23 PRINT *, 'ptot0 = ', ptot0
101     PRINT *, 'etot0 = ', etot0
102     PRINT *, 'ztot0 = ', ztot0
103     PRINT *, 'stot0 = ', stot0
104     PRINT *, 'ang0 = ', ang0
105 guez 3
106 guez 23 END SUBROUTINE sortvarc0

  ViewVC Help
Powered by ViewVC 1.1.21