/[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 258 by guez, Tue Mar 6 15:17:17 2018 UTC revision 259 by guez, Tue Mar 6 16:19:52 2018 UTC
# Line 2  module sortvarc_m Line 2  module sortvarc_m
2    
3    IMPLICIT NONE    IMPLICIT NONE
4    
   real, save:: ang, etot, ptot, ztot, stot, rmsdpdt, rmsv  
   
5  contains  contains
6    
7    SUBROUTINE sortvarc(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, &    SUBROUTINE sortvarc(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, &
8         resetvarc)         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
# Line 17  contains Line 15  contains
15      USE comgeom, ONLY: aire_2d, cu_2d      USE comgeom, ONLY: aire_2d, cu_2d
16      USE dimens_m, ONLY: iim, jjm, llm      USE dimens_m, ONLY: iim, jjm, llm
17      use dynetat0_m, ONLY: rlatu      use dynetat0_m, ONLY: rlatu
     USE ener, ONLY: ang0, etot0, ptot0, stot0, ztot0  
18      use filtreg_scal_m, only: filtreg_scal      use filtreg_scal_m, only: filtreg_scal
19      use massbarxy_m, only: massbarxy      use massbarxy_m, only: massbarxy
20      USE paramet_m, ONLY: jjp1      USE paramet_m, ONLY: jjp1
# Line 32  contains Line 29  contains
29      REAL, intent(in):: phi(iim + 1, jjm + 1, llm)      REAL, intent(in):: phi(iim + 1, jjm + 1, llm)
30      real, intent(in):: bern(iim + 1, jjm + 1, llm)      real, intent(in):: bern(iim + 1, jjm + 1, llm)
31      REAL, intent(in):: dp(iim + 1, jjm + 1)      REAL, intent(in):: dp(iim + 1, jjm + 1)
32      logical, intent(in):: resetvarc      real, intent(out):: ang, etot, ptot, ztot, stot, rmsdpdt, rmsv
33    
34      ! Local:      ! Local:
35      REAL bernf(iim + 1, jjm + 1, llm)      REAL bernf(iim + 1, jjm + 1, llm)
# Line 81  contains Line 78  contains
78      rmsv = 2. &      rmsv = 2. &
79           * sum(masse(:iim, :, :) * max(bernf(:iim, :, :) - phi(:iim, :, :), 0.))           * sum(masse(:iim, :, :) * max(bernf(:iim, :, :) - phi(:iim, :, :), 0.))
80    
     IF (resetvarc .or. ptot0 == 0.) then  
        print *, 'sortvarc: recomputed initial values.'  
        etot0 = etot  
        ptot0 = ptot  
        ztot0 = ztot  
        stot0 = stot  
        ang0  = ang  
        PRINT *, 'ptot0 = ', ptot0  
        PRINT *, 'etot0 = ', etot0  
        PRINT *, 'ztot0 = ', ztot0  
        PRINT *, 'stot0 = ', stot0  
        PRINT *, 'ang0 = ', ang0  
     END IF  
   
     IF (.not. resetvarc) then  
        etot = etot / etot0  
        rmsv = sqrt(rmsv / ptot)  
        ptot = ptot / ptot0  
        ztot = ztot / ztot0  
        stot = stot / stot0  
        ang = ang / ang0  
     end IF  
   
81    END SUBROUTINE sortvarc    END SUBROUTINE sortvarc
82    
83  end module sortvarc_m  end module sortvarc_m

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

  ViewVC Help
Powered by ViewVC 1.1.21