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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 64 - (hide annotations)
Wed Aug 29 14:47:17 2012 UTC (11 years, 9 months ago) by guez
File size: 3049 byte(s)
Removed variable lstardis in module comdissnew and procedures gradiv
and nxgrarot. lstardir had to be true. gradiv and nxgrarot were called
if lstardis was false. Removed argument iter of procedure
filtreg. iter had to be 1. gradiv and nxgrarot called filtreg with
iter == 2.

Moved procedure flxsetup into module yoecumf. Module yoecumf is only
used in program units of directory Conflx, moved it there.

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

  ViewVC Help
Powered by ViewVC 1.1.21