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

    r2335 r2336  
     1SUBROUTINE vitvert (convm, w)
    12!
    2 ! $Header$
    3 !
    4       SUBROUTINE vitvert ( convm , w )
    5 c
    6       IMPLICIT NONE
     3!-------------------------------------------------------------------------------
     4! Authors: P. Le Van , Fr. Hourdin.
     5!-------------------------------------------------------------------------------
     6! Purpose: Compute vertical speed at sigma levels.
     7  IMPLICIT NONE
     8  include "dimensions.h"
     9  include "paramet.h"
     10  include "comvert.h"
     11!===============================================================================
     12! Arguments:
     13  REAL, INTENT(IN)  :: convm(ip1jmp1,llm)
     14  REAL, INTENT(OUT) :: w    (ip1jmp1,llm)
     15!===============================================================================
     16! Notes: Vertical speed is oriented from bottom to top.
     17!   * At ground - level sigma(1):     w(i,j,1) = 0.
     18!   * At top    - level sigma(llm+1): w(i,j,l) = 0. (not stored in w)
     19!===============================================================================
     20! Local variables:
     21  INTEGER :: l
     22!===============================================================================
     23  DO l=1,llmm1; w(:,l+1)=convm(:,l+1)-bp(l+1)*convm(:,1); END DO
     24  w(:,1)=0.
    725
    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 vitesse verticale aux niveaux sigma  ....
    18 c    *******************************************************************
    19 c     convm   est un argument  d'entree pour le s-pg  ......
    20 c       w     est un argument de sortie pour le s-pg  ......
    21 c
    22 c    la vitesse verticale est orientee de  haut en bas .
    23 c    au sol, au niveau sigma(1),   w(i,j,1) = 0.
    24 c    au sommet, au niveau sigma(llm+1) , la vit.verticale est aussi
    25 c    egale a 0. et n'est pas stockee dans le tableau w  .
    26 c
    27 c
    28 c=======================================================================
     26END SUBROUTINE vitvert
    2927
    30 #include "dimensions.h"
    31 #include "paramet.h"
    32 #include "comvert.h"
    33 
    34       REAL w(ip1jmp1,llm),convm(ip1jmp1,llm)
    35       INTEGER   l, ij
    36 
    37 
    38 
    39       DO 2  l = 1,llmm1
    40 
    41       DO 1 ij = 1,ip1jmp1
    42       w( ij, l+1 ) = convm( ij, l+1 ) - bp(l+1) * convm( ij, 1 )
    43    1  CONTINUE
    44 
    45    2  CONTINUE
    46 
    47       DO 5 ij  = 1,ip1jmp1
    48       w(ij,1)  = 0.
    49 5     CONTINUE
    50 
    51       RETURN
    52       END
Note: See TracChangeset for help on using the changeset viewer.