/[lmdze]/trunk/libf/dyn3d/caldyn.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/caldyn.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 10 - (show annotations)
Fri Apr 18 14:45:53 2008 UTC (16 years ago) by guez
Original Path: trunk/libf/dyn3d/caldyn.f
File size: 3859 byte(s)
Added NetCDF directory "/home/guez/include" in "g95.mk" and
"nag_tools.mk".

Added some "intent" attributes in "PVtheta", "advtrac", "caladvtrac",
"calfis", "diagedyn", "dissip", "vlspltqs", "aeropt", "ajsec",
"calltherm", "clmain", "cltrac", "cltracrn", "concvl", "conema3",
"conflx", "fisrtilp", "newmicro", "nuage", "diagcld1", "diagcld2",
"drag_noro", "lift_noro", "SUGWD", "physiq", "phytrac", "radlwsw", "thermcell".

Removed the case "ierr == 0" in "abort_gcm"; moved call to "histclo"
and messages for end of run from "abort_gcm" to "gcm"; replaced call
to "abort_gcm" in "leapfrog" by exit from outer loop.

In "calfis": removed argument "pp" and variable "unskap"; changed
"pksurcp" from scalar to rank 2; use "pressure_var"; rewrote
computation of "zplev", "zplay", "ztfi", "pcvgt" using "dyn_phy";
added computation of "pls".

Removed unused variable in "dynredem0".

In "exner_hyb": changed "dellta" from scalar to rank 1; replaced call
to "ssum" by call to "sum"; removed variables "xpn" and "xps";
replaced some loops by array expressions.

In "leapfrog": use "pressure_var"; deleted variables "p", "longcles".

Converted common blocks "YOECUMF", "YOEGWD" to modules.

Removed argument "pplay" in "cvltr", "diagetpq", "nflxtr".

Created module "raddimlw" from include file "raddimlw.h".

Corrected call to "new_unit" in "test_disvert".

1 !
2 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/caldyn.F,v 1.1.1.1 2004/05/19 12:53:06 lmdzadmin Exp $
3 !
4 c
5 c
6 SUBROUTINE caldyn
7 $ (itau,ucov,vcov,teta,ps,masse,pk,pkf,phis ,
8 $ phi,conser,du,dv,dteta,dp,w,pbaru,pbarv,time )
9
10 use dimens_m
11 use paramet_m
12 use comconst
13 use comvert
14 use comgeom
15 use pression_m, only: pression
16
17 IMPLICIT NONE
18
19 c=======================================================================
20 c
21 c Auteur : P. Le Van
22 c
23 c Objet:
24 c ------
25 c
26 c Calcul des tendances dynamiques.
27 c
28 c Modif 04/93 F.Forget
29 c=======================================================================
30
31 c-----------------------------------------------------------------------
32 c 0. Declarations:
33 c ----------------
34
35
36 c Arguments:
37 c ----------
38
39 LOGICAL conser
40
41 INTEGER, intent(in):: itau
42 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)
43 REAL ps(ip1jmp1),phis(ip1jmp1)
44 REAL, intent(in):: pk(iip1,jjp1,llm)
45 real pkf(ip1jmp1,llm)
46 REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
47 REAL phi(ip1jmp1,llm),masse(ip1jmp1,llm)
48 REAL dv(ip1jm,llm),du(ip1jmp1,llm)
49 REAL dteta(ip1jmp1,llm),dp(ip1jmp1)
50 REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)
51 REAL time
52
53 c Local:
54 c ------
55
56 REAL ang(ip1jmp1,llm),p(ip1jmp1,llmp1)
57 REAL massebx(ip1jmp1,llm),masseby(ip1jm,llm),psexbarxy(ip1jm)
58 REAL vorpot(ip1jm,llm)
59 REAL w(ip1jmp1,llm),ecin(ip1jmp1,llm),convm(ip1jmp1,llm)
60 REAL bern(ip1jmp1,llm)
61 REAL massebxy(ip1jm,llm)
62
63 INTEGER ij,l
64
65 c-----------------------------------------------------------------------
66 c Calcul des tendances dynamiques:
67 c --------------------------------
68
69 CALL covcont ( llm , ucov , vcov , ucont, vcont )
70 CALL pression ( ip1jmp1, ap , bp , ps , p )
71 CALL psextbar ( ps , psexbarxy )
72 CALL massdair ( p , masse )
73 CALL massbar ( masse, massebx , masseby )
74 call massbarxy( masse, massebxy )
75 CALL flumass ( massebx, masseby , vcont, ucont ,pbaru, pbarv )
76 CALL dteta1 ( teta , pbaru , pbarv, dteta )
77 CALL convmas ( pbaru, pbarv , convm )
78
79 DO ij =1, ip1jmp1
80 dp( ij ) = convm( ij,1 ) / airesurg( ij )
81 ENDDO
82
83 CALL vitvert ( convm , w )
84 CALL tourpot ( vcov , ucov , massebxy , vorpot )
85 CALL dudv1 ( vorpot , pbaru , pbarv , du , dv )
86 CALL enercin ( vcov , ucov , vcont , ucont , ecin )
87 CALL bernoui ( ip1jmp1, llm , phi , ecin , bern )
88 CALL dudv2 ( teta , pkf , bern , du , dv )
89
90
91 DO l=1,llm
92 DO ij=1,ip1jmp1
93 ang(ij,l) = ucov(ij,l) + constang(ij)
94 ENDDO
95 ENDDO
96
97
98 CALL advect( ang, vcov, teta, w, massebx, masseby, du, dv,dteta )
99
100 C WARNING probleme de peridocite de dv sur les PC/linux. Pb d'arrondi
101 C probablement. Observe sur le code compile avec pgf90 3.0-1
102
103 DO l = 1, llm
104 DO ij = 1, ip1jm, iip1
105 IF( dv(ij,l).NE.dv(ij+iim,l) ) THEN
106 c PRINT *,'!!!ATTENTION!!! probleme de periodicite sur vcov',
107 c , ' dans caldyn'
108 c PRINT *,' l, ij = ', l, ij, ij+iim,dv(ij+iim,l),dv(ij,l)
109 dv(ij+iim,l) = dv(ij,l)
110 endif
111 enddo
112 enddo
113 c-----------------------------------------------------------------------
114 c Sorties eventuelles des variables de controle:
115 c ----------------------------------------------
116
117 IF( conser ) THEN
118 CALL sortvarc
119 $ ( itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time,vcov )
120
121 ENDIF
122
123 RETURN
124 END

  ViewVC Help
Powered by ViewVC 1.1.21