Ignore:
Timestamp:
Jul 31, 2015, 7:22:21 PM (9 years ago)
Author:
dcugnet
Message:
  • Add parallel capability for ce0l.
  • Small bug in grid_noro fixed (smoothed topography was used instead of unsmoothed one for geopotential computation at north pole).
  • Removed average of mass at poles in etat0dyn_netcdf after start_init_dyn => different results in the zoomed grid case.
  • ok_etat0=n and ok_limit=y combination now works fine (if no initial state is needed, but only limit.nc file). This required:
    • to move grid_noro0 and start_init_noro0 subroutines from etat0dyn_netcdf.F90 to limit_netcdf.F90
    • to create init_ssrf_m.F90 file, so that sub-surfaces can be initialized from limit_netcdf.F90 without any etat0*_netcdf routines call).
  • Simplified somehow the corresponding code, in particular: 1) removed obsolete flags "oldice". 2) removed flag "ibar": barycentric interpolation is used everywhere (except in start_init_subsurf, still calling grille_m - to be changed soon). 3) removed useless CPP_PHY precompilation directives, considering the possibility to run ce0l without physics is useless (ce0l is dedicated to Earth physics).
File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d_common/convmas.F90

    r2335 r2336  
     1SUBROUTINE convmas (pbaru, pbarv, convm)
    12!
    2 ! $Header$
    3 !
    4       SUBROUTINE convmas (pbaru, pbarv, convm )
    5 c
    6       IMPLICIT NONE
     3!-------------------------------------------------------------------------------
     4! Authors: P. Le Van , Fr. Hourdin.
     5!-------------------------------------------------------------------------------
     6! Purpose: Compute mass flux convergence at p levels.
     7  IMPLICIT NONE
     8  include "dimensions.h"
     9  include "paramet.h"
     10  include "comgeom.h"
     11  include "logic.h"
     12!===============================================================================
     13! Arguments:
     14  REAL, INTENT(IN)  :: pbaru(ip1jmp1,llm)
     15  REAL, INTENT(IN)  :: pbarv(ip1jm  ,llm)
     16  REAL, INTENT(OUT) :: convm(ip1jmp1,llm)
     17!===============================================================================
     18! Method used:   Computation from top to bottom.
     19!   Mass convergence at level llm is equal to zero and is not stored in convm.
     20!===============================================================================
     21! Local variables:
     22  INTEGER :: l
     23!===============================================================================
    724
    8 c=======================================================================
    9 c
    10 c   Auteurs:  P. Le Van , F. Hourdin  .
    11 c   -------
    12 c
    13 c   Objet:
    14 c   ------
    15 c
    16 c   ********************************************************************
    17 c   .... calcul de la convergence du flux de masse aux niveaux p ...
    18 c   ********************************************************************
    19 c
    20 c
    21 c     pbaru  et  pbarv  sont des arguments d'entree pour le s-pg  ....
    22 c      .....  convm      est  un argument de sortie pour le s-pg  ....
    23 c
    24 c    le calcul se fait de haut en bas,
    25 c    la convergence de masse au niveau p(llm+1) est egale a 0. et
    26 c    n'est pas stockee dans le tableau convm .
    27 c
    28 c
    29 c=======================================================================
    30 c
    31 c   Declarations:
    32 c   -------------
     25!--- Computation of - (d(pbaru)/dx + d(pbarv)/dy )
     26  CALL convflu( pbaru, pbarv, llm, convm )
    3327
    34 #include "dimensions.h"
    35 #include "paramet.h"
    36 #include "comvert.h"
    37 #include "logic.h"
     28!--- Filter
     29  CALL filtreg( convm, jjp1, llm, 2, 2, .TRUE., 1 )
    3830
    39       REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm ),convm(  ip1jmp1,llm )
    40       INTEGER   l,ij
     31!--- Mass convergence is integrated from top to bottom
     32  DO l=llmm1,1,-1
     33    convm(:,l) = convm(:,l) + convm(:,l+1)
     34  END DO
    4135
    42 
    43 c-----------------------------------------------------------------------
    44 c    ....  calcul de - (d(pbaru)/dx + d(pbarv)/dy ) ......
    45 
    46       CALL  convflu( pbaru, pbarv, llm, convm )
    47 
    48 c-----------------------------------------------------------------------
    49 c   filtrage:
    50 c   ---------
    51 
    52        CALL filtreg( convm, jjp1, llm, 2, 2, .true., 1 )
    53 
    54 c    integration de la convergence de masse de haut  en bas ......
    55 
    56       DO      l      = llmm1, 1, -1
    57         DO    ij     = 1, ip1jmp1
    58          convm(ij,l) = convm(ij,l) + convm(ij,l+1)
    59         ENDDO
    60       ENDDO
    61 c
    62       RETURN
    63       END
     36END SUBROUTINE convmas
Note: See TracChangeset for help on using the changeset viewer.