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

Diff of /trunk/dyn3d/sortvarc.f

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

trunk/libf/dyn3d/sortvarc.f90 revision 33 by guez, Fri Apr 9 10:56:14 2010 UTC trunk/dyn3d/sortvarc.f revision 259 by guez, Tue Mar 6 16:19:52 2018 UTC
# Line 4  module sortvarc_m Line 4  module sortvarc_m
4    
5  contains  contains
6    
7    SUBROUTINE sortvarc(itau, ucov, teta, ps, masse, pk, phis, vorpot, phi, &    SUBROUTINE sortvarc(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, &
8         bern, dp, time_0)         ang, etot, ptot, ztot, stot, rmsdpdt, rmsv)
9    
10      ! 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
11      ! Author: P. Le Van      ! Author: P. Le Van
12      ! Objet : sortie des variables de contrôle      ! Objet : sortie des variables de contr\^ole
13    
14      USE conf_gcm_m, ONLY: day_step      USE comconst, ONLY: daysec, g, omeg, rad
15      USE dimens_m, ONLY : iim, jjm, llm      USE comgeom, ONLY: aire_2d, cu_2d
16      USE paramet_m, ONLY : iip1, iip2, ijp1llm, ip1jm, ip1jmp1, jjp1      USE dimens_m, ONLY: iim, jjm, llm
17      USE comconst, ONLY : daysec, dtvr, g, omeg, rad      use dynetat0_m, ONLY: rlatu
18      USE comgeom, ONLY : aire, cu, rlatu      use filtreg_scal_m, only: filtreg_scal
19      USE dynetat0_m, ONLY : day_ini      use massbarxy_m, only: massbarxy
20      USE ener, ONLY : ang, ang0, etot, etot0, ptot, ptot0, rmsdpdt, rmsv, &      USE paramet_m, ONLY: jjp1
21           stot, stot0, ztot, ztot0  
22      use filtreg_m, only: filtreg      REAL, INTENT(IN):: ucov(iim + 1, jjm + 1, llm)
23        REAL, INTENT(IN):: teta(iim + 1, jjm + 1, llm)
24      ! Arguments:      REAL, INTENT(IN):: ps(iim + 1, jjm + 1)
25      INTEGER, INTENT (IN) :: itau      REAL, INTENT(IN):: masse(iim + 1, jjm + 1, llm)
26      REAL :: ucov(ip1jmp1, llm), teta(ip1jmp1, llm), masse(ip1jmp1, llm)      REAL, INTENT(IN):: pk(iim + 1, jjm + 1, llm)
27      REAL :: ps(ip1jmp1), phis(ip1jmp1)      REAL, INTENT(IN):: phis(iim + 1, jjm + 1)
28      REAL :: vorpot(ip1jm, llm)      REAL, INTENT(IN):: vorpot(:, :, :) ! (iim + 1, jjm, llm)
29      REAL :: phi(ip1jmp1, llm), bern(ip1jmp1, llm)      REAL, intent(in):: phi(iim + 1, jjm + 1, llm)
30      REAL :: dp(ip1jmp1)      real, intent(in):: bern(iim + 1, jjm + 1, llm)
31      REAL, INTENT (IN):: time_0      REAL, intent(in):: dp(iim + 1, jjm + 1)
32      REAL, INTENT (IN):: pk(ip1jmp1, llm)      real, intent(out):: ang, etot, ptot, ztot, stot, rmsdpdt, rmsv
33    
34      ! Local:      ! Local:
35      REAL :: vor(ip1jm), bernf(ip1jmp1, llm), ztotl(llm)      REAL bernf(iim + 1, jjm + 1, llm)
36      REAL :: etotl(llm), stotl(llm), rmsvl(llm), angl(llm), ge(ip1jmp1)      REAL etotl(llm), angl(llm), ge(iim, 2:jjm)
37      REAL :: cosphi(ip1jm), omegcosp(ip1jm)      REAL cosphi(2:jjm)
38      REAL :: dtvrs1j, rjour, heure, radsg, radomeg      REAL radsg, radomeg
39      real massebxy(ip1jm, llm)      REAL massebxy(iim + 1, jjm, llm)
40      INTEGER :: l, ij, imjmp1      INTEGER j, l
     REAL :: ssum  
     real time  
41    
42      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
43    
44      time = real(itau) / day_step + time_0      PRINT *, "Call sequence information: sortvarc"
     dtvrs1j = dtvr/daysec  
     rjour = real(int(itau*dtvrs1j))  
     heure = (itau*dtvrs1j-rjour)*24.  
     imjmp1 = iim*jjp1  
     IF (abs(heure-24.)<=0.0001) heure = 0.  
45    
46      CALL massbarxy(masse, massebxy)      rmsdpdt = daysec * 0.01 * sqrt(sum(dp(:iim, :)**2) / (iim * jjp1))
47    
48      ! Calcul  de  rmsdpdt      ! Calcul du moment  angulaire :
49      ge(:) = dp(:)*dp(:)      
50      rmsdpdt = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)      radsg = rad / g
51      rmsdpdt = daysec*1.E-2*sqrt(rmsdpdt/imjmp1)      radomeg = rad * omeg
52      CALL scopy(ijp1llm, bern, 1, bernf, 1)      cosphi = cos(rlatu(2:jjm))
     CALL filtreg(bernf, jjp1, llm, -2, 2, .TRUE., 1)  
   
     ! Calcul du moment  angulaire  
     radsg = rad/g  
     radomeg = rad*omeg  
     DO ij = iip2, ip1jm  
        cosphi(ij) = cos(rlatu((ij-1)/iip1+1))  
        omegcosp(ij) = radomeg*cosphi(ij)  
     END DO  
53    
     ! Calcul  de l'energie, de l'enstrophie, de l'entropie et de rmsv  
54      DO l = 1, llm      DO l = 1, llm
55         DO ij = 1, ip1jm         forall (j = 2:jjm) ge(:, j) = (ucov(:iim, j, l) / cu_2d(:iim, j) &
56            vor(ij) = vorpot(ij, l)*vorpot(ij, l)*massebxy(ij, l)              + radomeg * cosphi(j)) * masse(:iim, j, l) * cosphi(j)
57         END DO         angl(l) = radsg * sum(ge)
        ztotl(l) = (ssum(ip1jm, vor, 1)-ssum(jjm, vor, iip1))  
   
        DO ij = 1, ip1jmp1  
           ge(ij) = masse(ij, l) * (phis(ij) + teta(ij, l) * pk(ij, l) &  
                + bernf(ij, l)-phi(ij, l))  
        END DO  
        etotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)  
   
        DO ij = 1, ip1jmp1  
           ge(ij) = masse(ij, l)*teta(ij, l)  
        END DO  
        stotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)  
   
        DO ij = 1, ip1jmp1  
           ge(ij) = masse(ij, l)*amax1(bernf(ij, l)-phi(ij, l), 0.)  
        END DO  
        rmsvl(l) = 2.*(ssum(ip1jmp1, ge, 1)-ssum(jjp1, ge, iip1))  
   
        DO ij = iip2, ip1jm  
           ge(ij) = (ucov(ij, l)/cu(ij)+omegcosp(ij))*masse(ij, l)*cosphi(ij)  
        END DO  
        angl(l) = radsg * (ssum(ip1jm-iip1, ge(iip2), 1) &  
             - ssum(jjm-1, ge(iip2), iip1))  
58      END DO      END DO
59    
60      DO ij = 1, ip1jmp1      ang = sum(angl)
61         ge(ij) = ps(ij)*aire(ij)  
62      END DO      ! Calcul  de l'energie, de l'enstrophie, de l'entropie et de rmsv :
63      ptot = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)  
64      etot = ssum(llm, etotl, 1)      bernf = bern
65      ztot = ssum(llm, ztotl, 1)      CALL filtreg_scal(bernf, direct = .false., intensive = .false.)
66      stot = ssum(llm, stotl, 1)  
67      rmsv = ssum(llm, rmsvl, 1)      ptot = sum(ps(:iim, :) * aire_2d(:iim, :))
68      ang = ssum(llm, angl, 1)  
69        forall (l = 1:llm) etotl(l) = sum(masse(:iim, :, l) * (phis(:iim, :) &
70      IF (ptot0 == 0.) THEN           + teta(:iim, :, l) * pk(:iim, :, l) + bernf(:iim, :, l) &
71         PRINT *, 'WARNING!!! On recalcule les valeurs initiales de :'           - phi(:iim, :, l)))
72         PRINT *, 'ptot, rmsdpdt, etot, ztot, stot, rmsv, ang'      etot = sum(etotl)
73         PRINT *, ptot, rmsdpdt, etot, ztot, stot, rmsv, ang  
74         etot0 = etot      CALL massbarxy(masse, massebxy)
75         ptot0 = ptot      ztot = sum(vorpot(:iim, :, :)**2 * massebxy(:iim, :, :))
76         ztot0 = ztot  
77         stot0 = stot      stot = sum(masse(:iim, :, :) * teta(:iim, :, :))
78         ang0 = ang      rmsv = 2. &
79      END IF           * sum(masse(:iim, :, :) * max(bernf(:iim, :, :) - phi(:iim, :, :), 0.))
   
     etot = etot/etot0  
     rmsv = sqrt(rmsv/ptot)  
     ptot = ptot/ptot0  
     ztot = ztot/ztot0  
     stot = stot/stot0  
     ang = ang/ang0  
   
     PRINT 3500, itau, int(day_ini + time), heure, time  
     PRINT 4000, ptot, rmsdpdt, etot, ztot, stot, rmsv, ang  
   
 3500 FORMAT (4X, 'pas', I7, 5X, 'jour', i5, 1X, 'heure', F5.1, 4X, 'date', &  
           F10.5)  
 4000 FORMAT (10X, 'masse', 4X, 'rmsdpdt', 7X, 'energie', 2X, 'enstrophie', &  
           2X, 'entropie', 3X, 'rmsv', 4X, 'mt.ang', /, 'GLOB  ', F10.6, &  
           E13.6, 5F10.3/)  
80    
81    END SUBROUTINE sortvarc    END SUBROUTINE sortvarc
82    

Legend:
Removed from v.33  
changed lines
  Added in v.259

  ViewVC Help
Powered by ViewVC 1.1.21