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

Diff of /trunk/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 254 by guez, Mon Feb 5 10:39:38 2018 UTC revision 257 by guez, Tue Mar 6 14:49:28 2018 UTC
# Line 6  module sortvarc_m Line 6  module sortvarc_m
6    
7  contains  contains
8    
9    SUBROUTINE sortvarc(ucov, teta, ps, masse, pk, phis, vorpot, phi, &    SUBROUTINE sortvarc(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, &
10         bern, dp, resetvarc)         resetvarc)
11    
12      ! From dyn3d/sortvarc.F, version 1.1.1.1 2004/05/19 12:53:07      ! From dyn3d/sortvarc.F, version 1.1.1.1, 2004/05/19 12:53:07
13      ! Author: P. Le Van      ! Author: P. Le Van
14      ! Objet : sortie des variables de contr\^ole      ! Objet : sortie des variables de contr\^ole
15    
# Line 20  contains Line 20  contains
20      USE ener, ONLY: ang0, etot0, ptot0, stot0, ztot0      USE ener, ONLY: ang0, etot0, ptot0, stot0, ztot0
21      use filtreg_scal_m, only: filtreg_scal      use filtreg_scal_m, only: filtreg_scal
22      use massbarxy_m, only: massbarxy      use massbarxy_m, only: massbarxy
23      USE paramet_m, ONLY: iip1, ip1jm, jjp1      USE paramet_m, ONLY: jjp1
24    
25      REAL, INTENT(IN):: ucov(iim + 1, jjm + 1, llm)      REAL, INTENT(IN):: ucov(iim + 1, jjm + 1, llm)
26      REAL, INTENT(IN):: teta(iim + 1, jjm + 1, llm)      REAL, INTENT(IN):: teta(iim + 1, jjm + 1, llm)
# Line 28  contains Line 28  contains
28      REAL, INTENT(IN):: masse(iim + 1, jjm + 1, llm)      REAL, INTENT(IN):: masse(iim + 1, jjm + 1, llm)
29      REAL, INTENT(IN):: pk(iim + 1, jjm + 1, llm)      REAL, INTENT(IN):: pk(iim + 1, jjm + 1, llm)
30      REAL, INTENT(IN):: phis(iim + 1, jjm + 1)      REAL, INTENT(IN):: phis(iim + 1, jjm + 1)
31      REAL, INTENT(IN):: vorpot(ip1jm, llm)      REAL, INTENT(IN):: vorpot(:, :, :) ! (iim + 1, jjm, llm)
32      REAL, intent(in):: phi(iim + 1, jjm + 1, llm)      REAL, intent(in):: phi(iim + 1, jjm + 1, llm)
33      real, intent(in):: bern(iim + 1, jjm + 1, llm)      real, intent(in):: bern(iim + 1, jjm + 1, llm)
34      REAL, intent(in):: dp(iim + 1, jjm + 1)      REAL, intent(in):: dp(iim + 1, jjm + 1)
35      logical, intent(in):: resetvarc      logical, intent(in):: resetvarc
36    
37      ! Local:      ! Local:
38      REAL vor(ip1jm), bernf(iim + 1, jjm + 1, llm), ztotl(llm)      REAL bernf(iim + 1, jjm + 1, llm)
39      REAL etotl(llm), stotl(llm), rmsvl(llm), angl(llm), ge(iim + 1, jjm + 1)      REAL etotl(llm), stotl(llm), rmsvl(llm), angl(llm), ge(iim, 2:jjm)
40      REAL cosphi(2:jjm)      REAL cosphi(2:jjm)
41      REAL radsg, radomeg      REAL radsg, radomeg
42      REAL massebxy(ip1jm, llm)      REAL massebxy(iim + 1, jjm, llm)
43      INTEGER j, l, ij      INTEGER j, l
     REAL ssum  
44    
45      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
46    
# Line 50  contains Line 49  contains
49      CALL massbarxy(masse, massebxy)      CALL massbarxy(masse, massebxy)
50    
51      ! Calcul  de  rmsdpdt      ! Calcul  de  rmsdpdt
52      ge = dp*dp      rmsdpdt = sum(dp(:iim, :)**2)
53      rmsdpdt = sum(ge) - sum(ge(1, :))      rmsdpdt = daysec * 1.E-2 * sqrt(rmsdpdt / (iim * jjp1))
     rmsdpdt = daysec*1.E-2*sqrt(rmsdpdt / (iim * jjp1))  
54      bernf = bern      bernf = bern
55      CALL filtreg_scal(bernf, direct = .false., intensive = .false.)      CALL filtreg_scal(bernf, direct = .false., intensive = .false.)
56    
57      ! Calcul du moment  angulaire      ! Calcul du moment  angulaire
58      radsg = rad/g      radsg = rad/g
59      radomeg = rad*omeg      radomeg = rad * omeg
60      cosphi = cos(rlatu(2:jjm))      cosphi = cos(rlatu(2:jjm))
61    
62      ! Calcul  de l'energie, de l'enstrophie, de l'entropie et de rmsv      ! Calcul  de l'energie, de l'enstrophie, de l'entropie et de rmsv
63    
64      DO l = 1, llm      DO l = 1, llm
65         DO ij = 1, ip1jm         etotl(l) = sum(masse(:iim, :, l) * (phis(:iim, :) + teta(:iim, :, l) &
66            vor(ij) = vorpot(ij, l)*vorpot(ij, l)*massebxy(ij, l)              * pk(:iim, :, l) + bernf(:iim, :, l) - phi(:iim, :, l)))
67         END DO         stotl(l) = sum(masse(:iim, :, l) * teta(:iim, :, l))
68         ztotl(l) = (ssum(ip1jm, vor, 1)-ssum(jjm, vor, iip1))         rmsvl(l) = 2. * sum(masse(:iim, :, l) &
69                * max(bernf(:iim, :, l) - phi(:iim, :, l), 0.))
70         ge = masse(:, :, l) * (phis + teta(:, :, l) * pk(:, :, l) &  
71              + bernf(:, :, l) - phi(:, :, l))         forall (j = 2:jjm) ge(:, j) = (ucov(:iim, j, l) / cu_2d(:iim, j) &
72         etotl(l) = sum(ge) - sum(ge(1, :))              + radomeg * cosphi(j)) * masse(:iim, j, l) * cosphi(j)
73           angl(l) = radsg * sum(ge)
        ge = masse(:, :, l)*teta(:, :, l)  
        stotl(l) = sum(ge) - sum(ge(1, :))  
   
        ge = masse(:, :, l) * max(bernf(:, :, l) - phi(:, :, l), 0.)  
        rmsvl(l) = 2.*(sum(ge)-sum(ge(1, :)))  
   
        forall (j = 2:jjm) ge(:, j) = (ucov(:, j, l) / cu_2d(:, j) &  
             + radomeg * cosphi(j)) * masse(:, j, l) * cosphi(j)  
        angl(l) = radsg * (sum(ge(:, 2:jjm)) - sum(ge(1, 2:jjm)))  
74      END DO      END DO
75    
76      ge = ps * aire_2d      ptot = sum(ps(:iim, :) * aire_2d(:iim, :))
     ptot = sum(ge) - sum(ge(1, :))  
77      etot = sum(etotl)      etot = sum(etotl)
78      ztot = sum(ztotl)      ztot = sum(vorpot(:iim, :, :)**2 * massebxy(:iim, :, :))
79      stot = sum(stotl)      stot = sum(stotl)
80      rmsv = sum(rmsvl)      rmsv = sum(rmsvl)
81      ang = sum(angl)      ang = sum(angl)

Legend:
Removed from v.254  
changed lines
  Added in v.257

  ViewVC Help
Powered by ViewVC 1.1.21