source: LMDZ5/trunk/libf/dyn3d_common/caldyn0.F90 @ 2336

Last change on this file since 2336 was 2336, checked in by dcugnet, 9 years ago
  • 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 size: 3.1 KB
Line 
1SUBROUTINE caldyn0(itau,ucov,vcov,teta,ps,masse,pk,phis,phi,w,pbaru,pbarv,time)
2!
3!-------------------------------------------------------------------------------
4! Author: P. Le Van ; modif. 04/93: F.Forget.
5!-------------------------------------------------------------------------------
6! Purpose: Compute dynamic tendencies.
7!-------------------------------------------------------------------------------
8  USE control_mod, ONLY: resetvarc
9  IMPLICIT NONE
10  include "dimensions.h"
11  include "paramet.h"
12  include "comconst.h"
13  include "comvert.h"
14  include "comgeom.h"
15!===============================================================================
16! Arguments:
17  INTEGER, INTENT(IN)  :: itau                      !--- TIME STEP INDEX
18  REAL,    INTENT(IN)  :: vcov (ip1jm    ,llm)      !--- V COVARIANT WIND
19  REAL,    INTENT(IN)  :: ucov (ip1jmp1  ,llm)      !--- U COVARIANT WIND
20  REAL,    INTENT(IN)  :: teta (ip1jmp1  ,llm)      !--- POTENTIAL TEMPERATURE
21  REAL,    INTENT(IN)  :: ps   (ip1jmp1)            !--- GROUND PRESSURE
22  REAL,    INTENT(OUT) :: masse(ip1jmp1  ,llm)      !--- MASS IN EACH CELL
23  REAL,    INTENT(IN)  :: pk   (iip1,jjp1,llm)      !--- PRESSURE
24  REAL,    INTENT(IN)  :: phis (ip1jmp1)            !--- GROUND GEOPOTENTIAL
25  REAL,    INTENT(IN)  :: phi  (ip1jmp1  ,llm)      !--- 3D GEOPOTENTIAL
26  REAL,    INTENT(OUT) :: w    (ip1jmp1  ,llm)      !--- VERTICAL WIND
27  REAL,    INTENT(OUT) :: pbaru(ip1jmp1  ,llm)      !--- U MASS FLUX
28  REAL,    INTENT(OUT) :: pbarv(ip1jm    ,llm)      !--- V MASS FLUX
29  REAL,    INTENT(IN)  :: time                      !--- TIME
30!===============================================================================
31! Local variables:
32  REAL, DIMENSION(ip1jmp1,llmp1) :: p
33  REAL, DIMENSION(ip1jmp1,llm)   :: ucont, massebx, ang, ecin, convm, bern
34  REAL, DIMENSION(ip1jmp1)       :: dp
35  REAL, DIMENSION(ip1jm  ,llm)   :: vcont, masseby, massebxy, vorpot
36  REAL, DIMENSION(ip1jm)         :: psexbarxy
37  INTEGER                        :: ij, l
38!===============================================================================
39  CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
40  CALL pression ( ip1jmp1, ap      , bp   ,  ps  , p            )
41  CALL psextbar (   ps   , psexbarxy                            )
42  CALL massdair (    p   , masse                                )
43  CALL massbar  (   masse, massebx , masseby                    )
44  CALL massbarxy(   masse, massebxy                             )
45  CALL flumass  ( massebx, masseby , vcont, ucont ,pbaru, pbarv )
46  CALL convmas  (   pbaru, pbarv   , convm                      )
47  CALL vitvert  ( convm  , w                                    )
48  CALL tourpot  ( vcov   , ucov    , massebxy  , vorpot         )
49  CALL enercin  ( vcov   , ucov    , vcont     , ucont  , ecin  )
50  CALL bernoui  ( ip1jmp1, llm     , phi       , ecin   , bern  )
51  DO l=1,llm; ang(:,l) = ucov(:,l) + constang(:); END DO
52  resetvarc=.true. ! force a recomputation of initial values in sortvarc
53  dp(:)=convm(:,1)/airesurg(:)
54  CALL sortvarc( itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time,vcov )
55
56END SUBROUTINE caldyn0
Note: See TracBrowser for help on using the repository browser.