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

Last change on this file since 2334 was 2334, checked in by lguez, 9 years ago

Bug fix. maase, pbaru and pbarv cannot be intent(in) in caldyn0
because they are modified in caldyn0 (masse is computed by massdair
and pbaru, pbarv are computed by flumass). Also masse is already
computed in etat0dyn_netcdf, and the difference with the computation
in caldyn0 is the averaging at the poles. If we do not want to lose
this averaging, we should not overwrite masse with an output argument
from caldyn0. So the simplest thing to do is to downgrade masse from
argument to local variable of caldyn0. We also simply downgrade pbaru,
pbarv from arguments to local variables of caldyn0.

File size: 3.0 KB
Line 
1SUBROUTINE caldyn0(itau,ucov,vcov,teta,ps,pk,phis,phi,w,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                      !---
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(IN)  :: pk   (iip1,jjp1,llm)      !--- PRESSURE
23  REAL,    INTENT(IN)  :: phis (ip1jmp1)            !--- GROUND GEOPOTENTIAL
24  REAL,    INTENT(IN)  :: phi  (ip1jmp1  ,llm)      !--- 3D GEOPOTENTIAL
25  REAL,    INTENT(OUT) :: w    (ip1jmp1  ,llm)      !--- VERTICAL WIND
26  REAL,    INTENT(IN)  :: time                      !--- TIME
27!===============================================================================
28! Local variables:
29  REAL masse(ip1jmp1  ,llm)      !--- MASS IN EACH CELL
30  REAL pbaru(ip1jmp1  ,llm)      !--- U MASS FLUX
31  REAL pbarv(ip1jm    ,llm)      !--- V MASS FLUX
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.