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/convmas2_loc.F90

    r2335 r2336  
    1       SUBROUTINE convmas2_loc ( convm )
    2 c
    3       USE parallel_lmdz
    4       IMPLICIT NONE
     1SUBROUTINE convmas2_loc (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 convmas1_loc is called before.
     8  USE parallel_lmdz
     9  IMPLICIT NONE
     10  include "dimensions.h"
     11  include "paramet.h"
     12  include "comgeom.h"
     13  include "logic.h"
     14!===============================================================================
     15! Arguments:
     16  REAL, INTENT(INOUT) :: convm(ijb_u:ije_u,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, ijb, ije
     23!===============================================================================
    524
    6 c=======================================================================
    7 c
    8 c   Auteurs:  P. Le Van , F. Hourdin  .
    9 c   -------
    10 c
    11 c   Objet:
    12 c   ------
    13 c
    14 c   ********************************************************************
    15 c   .... calcul de la convergence du flux de masse aux niveaux p ...
    16 c   ********************************************************************
    17 c
    18 c
    19 c     pbaru  et  pbarv  sont des arguments d'entree pour le s-pg  ....
    20 c      .....  convm      est  un argument de sortie pour le s-pg  ....
    21 c
    22 c    le calcul se fait de haut en bas,
    23 c    la convergence de masse au niveau p(llm+1) est egale a 0. et
    24 c    n'est pas stockee dans le tableau convm .
    25 c
    26 c
    27 c=======================================================================
    28 c
    29 c   Declarations:
    30 c   -------------
     25!$OMP MASTER
     26!--- Mass convergence is integrated from top to bottom
     27  ijb=ij_begin
     28  ije=ij_end+iip1
     29  IF(pole_sud) ije=ij_end
     30  DO l=llmm1,1,-1
     31    convm(ijb:ije,l) = convm(ijb:ije,l) + convm(ijb:ije,l+1)
     32  END DO
     33!$OMP END MASTER
    3134
    32 #include "dimensions.h"
    33 #include "paramet.h"
    34 #include "comvert.h"
    35 #include "logic.h"
     35END SUBROUTINE convmas2_loc
    3636
    37       REAL pbaru( ijb_u:ije_u,llm ),pbarv( ijb_v:ije_v,llm )
    38       REAL :: convm(  ijb_u:ije_u,llm )
    39       INTEGER   l,ij
    40       INTEGER ijb,ije,jjb,jje
    41  
    42 c$OMP MASTER
    43 c    integration de la convergence de masse de haut  en bas ......
    44        ijb=ij_begin
    45        ije=ij_end+iip1
    46        if (pole_sud) ije=ij_end
    47            
    48       DO      l      = llmm1, 1, -1
    49         DO    ij     = ijb, ije
    50          convm(ij,l) = convm(ij,l) + convm(ij,l+1)
    51         ENDDO
    52       ENDDO
    53 c
    54 c$OMP END MASTER
    55       RETURN
    56       END
Note: See TracChangeset for help on using the changeset viewer.