/[lmdze]/trunk/dyn3d/Dissipation/divgrad2.f90
ViewVC logotype

Contents of /trunk/dyn3d/Dissipation/divgrad2.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 56 - (show annotations)
Tue Jan 10 19:02:02 2012 UTC (12 years, 5 months ago) by guez
Original Path: trunk/libf/dyn3d/Dissipation/divgrad2.f
File size: 2127 byte(s)
Imported "writehist.f" from LMDZ.

Moved module variable "histaveid" from "com_io_dyn" to "initdynav_m".

In "inithist", access directly module variables from "com_io_dyn"
instead of going through the arguments. Copying from LMDZ, write "u"
and scalar variables to separate files. Create a new variable for the
new file in "com_io_dyn". Copying from LMDZ, change the vertical axes
of the three files.

Removed some useless initializations in "dissip".

In "bilan_dyn", removed useless variable "time". Avoiding the
approximate test on "dt_cum" being a multiple of "dt_app", just
compute "ncum" from known usage of "bilan_dyn" and compute "dt_cum"
from "ncum". Change "periodav" from real to integer in
"conf_gcm_m". Since "day_step" is required to be a multiple of
"iperiod", so is "ncum".

1 !
2 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/divgrad2.F,v 1.1.1.1 2004/05/19 12:53:06 lmdzadmin Exp $
3 !
4 SUBROUTINE divgrad2 ( klevel, h, deltapres, lh, divgra, cdivh )
5 c
6 c P. Le Van
7 c
8 c ***************************************************************
9 c
10 c ..... calcul de (div( grad )) de ( pext * h ) .....
11 c ****************************************************************
12 c h ,klevel,lh et pext sont des arguments d'entree pour le s-prg
13 c divgra est un argument de sortie pour le s-prg
14 c
15 use dimens_m
16 use paramet_m
17 use comgeom
18 IMPLICIT NONE
19 c
20
21 c ....... variables en arguments .......
22 c
23 INTEGER klevel
24 REAL, intent(in):: h( ip1jmp1,klevel ), deltapres( ip1jmp1,klevel)
25 REAL, intent(out):: divgra( ip1jmp1,klevel)
26 real, intent(in):: cdivh
27 c
28 c ....... variables locales ..........
29 c
30 REAL signe, nudivgrs, sqrtps( ip1jmp1,llm )
31 INTEGER l,ij,iter
32 integer, intent(in):: lh
33 c ...................................................................
34
35 c
36 signe = (-1.)**lh
37 nudivgrs = signe * cdivh
38 divgra = h
39
40 c
41 CALL laplacien( klevel, divgra, divgra )
42
43 DO l = 1, klevel
44 DO ij = 1, ip1jmp1
45 sqrtps( ij,l ) = SQRT( deltapres(ij,l) )
46 ENDDO
47 ENDDO
48 c
49 DO l = 1, klevel
50 DO ij = 1, ip1jmp1
51 divgra(ij,l) = divgra(ij,l) * sqrtps(ij,l)
52 ENDDO
53 ENDDO
54
55 c ........ Iteration de l'operateur laplacien_gam ........
56 c
57 DO iter = 1, lh - 2
58 CALL laplacien_gam ( klevel,cuvscvgam2,cvuscugam2,unsair_gam2,
59 * unsapolnga2, unsapolsga2, divgra, divgra )
60 ENDDO
61 c
62 c ...............................................................
63
64 DO l = 1, klevel
65 DO ij = 1, ip1jmp1
66 divgra(ij,l) = divgra(ij,l) * sqrtps(ij,l)
67 ENDDO
68 ENDDO
69 c
70 CALL laplacien ( klevel, divgra, divgra )
71 c
72 DO l = 1,klevel
73 DO ij = 1,ip1jmp1
74 divgra(ij,l) = nudivgrs * divgra(ij,l) / deltapres(ij,l)
75 ENDDO
76 ENDDO
77
78 RETURN
79 END

  ViewVC Help
Powered by ViewVC 1.1.21