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/dyn3dmem/convmas1_loc.F90

    r2335 r2336  
    1       SUBROUTINE convmas1_loc (pbaru, pbarv, convm )
    2 c
    3       USE parallel_lmdz
    4       USE mod_filtreg_p
    5       IMPLICIT NONE
     1SUBROUTINE convmas1_loc (pbaru, pbarv, convm)
     2!
     3!-------------------------------------------------------------------------------
     4! Authors: P. Le Van , Fr. Hourdin.
     5!-------------------------------------------------------------------------------
     6! Purpose: Compute mass flux convergence at p levels.
     7!          Equivalent to convmas_loc if convmas2_loc is called after.
     8  USE parallel_lmdz
     9  USE mod_filtreg_p
     10  IMPLICIT NONE
     11  include "dimensions.h"
     12  include "paramet.h"
     13  include "comgeom.h"
     14  include "logic.h"
     15!===============================================================================
     16! Arguments:
     17  REAL, INTENT(IN)  :: pbaru(ijb_u:ije_u,llm)
     18  REAL, INTENT(IN)  :: pbarv(ijb_v:ije_v,llm)
     19  REAL, TARGET, INTENT(OUT) :: convm(ijb_u:ije_u,llm)
     20!===============================================================================
     21! Method used:   Computation from top to bottom.
     22!   Mass convergence at level llm is equal to zero and is not stored in convm.
     23!===============================================================================
     24! Local variables:
     25  INTEGER :: l, jjb, jje
     26!===============================================================================
    627
    7 c=======================================================================
    8 c
    9 c   Auteurs:  P. Le Van , F. Hourdin  .
    10 c   -------
    11 c
    12 c   Objet:
    13 c   ------
    14 c
    15 c   ********************************************************************
    16 c   .... calcul de la convergence du flux de masse aux niveaux p ...
    17 c   ********************************************************************
    18 c
    19 c
    20 c     pbaru  et  pbarv  sont des arguments d'entree pour le s-pg  ....
    21 c      .....  convm      est  un argument de sortie pour le s-pg  ....
    22 c
    23 c    le calcul se fait de haut en bas,
    24 c    la convergence de masse au niveau p(llm+1) est egale a 0. et
    25 c    n'est pas stockee dans le tableau convm .
    26 c
    27 c
    28 c=======================================================================
    29 c
    30 c   Declarations:
    31 c   -------------
     28!--- Computation of - (d(pbaru)/dx + d(pbarv)/dy )
     29  CALL convflu_loc( pbaru, pbarv, llm, convm )
    3230
    33 #include "dimensions.h"
    34 #include "paramet.h"
    35 #include "comvert.h"
    36 #include "logic.h"
     31!--- Filter
     32  jjb=jj_begin
     33  jje=jj_end+1
     34  IF(pole_sud) jje=jj_end
     35  CALL filtreg_p(convm,jjb_u,jje_u,jjb,jje,jjp1,llm,2,2,.TRUE.,1)
    3736
    38       REAL pbaru( ijb_u:ije_u,llm ),pbarv( ijb_v:ije_v,llm )
    39       REAL, target :: convm(  ijb_u:ije_u,llm )
    40       INTEGER   l,ij
     37END SUBROUTINE convmas1_loc
    4138
    42       INTEGER ijb,ije,jjb,jje
    43  
    44      
    45 c-----------------------------------------------------------------------
    46 c    ....  calcul de - (d(pbaru)/dx + d(pbarv)/dy ) ......
    47 
    48       CALL  convflu_loc( pbaru, pbarv, llm, convm )
    49 
    50 c-----------------------------------------------------------------------
    51 c   filtrage:
    52 c   ---------
    53        
    54        jjb=jj_begin
    55        jje=jj_end+1
    56        if (pole_sud) jje=jj_end
    57  
    58        CALL filtreg_p( convm, jjb_u,jje_u,jjb, jje, jjp1, llm,
    59      &                 2, 2, .true., 1 )
    60 
    61 c    integration de la convergence de masse de haut  en bas ......
    62 c
    63       RETURN
    64       END
Note: See TracChangeset for help on using the changeset viewer.