/[lmdze]/trunk/Sources/dyn3d/Vlsplt/vlsplt.f
ViewVC logotype

Annotation of /trunk/Sources/dyn3d/Vlsplt/vlsplt.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 157 - (hide annotations)
Mon Jul 20 16:01:49 2015 UTC (8 years, 10 months ago) by guez
File size: 1674 byte(s)
Just encapsulated SUBROUTINE vlsplt in a module and cleaned it.

In procedure vlx, local variables dxqu and adxqu only need indices
iip2:ip1jm. Otherwise, just cleaned vlx.

Procedures dynredem0 and dynredem1 no longer have argument fichnom,
they just operate on a file named "restart.nc". The programming
guideline here is that gcm should not be more complex than it needs by
itself, other programs (ce0l etc.) just have to adapt to gcm. So ce0l
now creates files "restart.nc" and "restartphy.nc".

In order to facilitate decentralizing the writing of "restartphy.nc",
created a procedure phyredem0 out of phyredem. phyredem0 creates the
NetCDF header of "restartphy.nc" while phyredem writes the NetCDF
variables. As the global attribute itau_phy needs to be filled in
phyredem0, at the beginnig of the run, we must compute its value
instead of just using itap. So we have a dummy argument lmt_pas of
phyredem0. Also, the ncid of "startphy.nc" is upgraded from local
variable of phyetat0 to dummy argument. phyetat0 no longer closes
"startphy.nc".

Following the same decentralizing objective, the ncid of "restart.nc"
is upgraded from local variable of dynredem0 to module variable of
dynredem0_m. "restart.nc" is not closed at the end of dynredem0 nor
opened at the beginning of dynredem1.

In procedure etat0, instead of creating many vectors of size klon
which will be filled with zeroes, just create one array null_array.

In procedure phytrac, instead of writing trs(: 1) to a text file,
write it to "restartphy.nc" (following LMDZ). This is better because
now trs(: 1) is next to its coordinates. We can write to
"restartphy.nc" from phytrac directly, and not add trs(: 1) to the
long list of variables in physiq, thanks to the decentralizing of
"restartphy.nc".

In procedure phyetat0, we no longer write to standard output the
minimum and maximum values of read arrays. It is ok to check input and
abort on invalid values but just printing statistics on input seems too
much useless computation and out of place clutter.

1 guez 157 module vlsplt_m
2 guez 3
3 guez 157 IMPLICIT NONE
4 guez 3
5 guez 157 contains
6 guez 3
7 guez 157 SUBROUTINE vlsplt(q, pente_max, masse, w, pbaru, pbarv, pdt)
8 guez 3
9 guez 157 ! From LMDZ4/libf/dyn3d/vlsplt.F, version 1.2 2005/02/24 12:16:57 fairhead
10 guez 3
11 guez 157 ! Authors: P. Le Van, F. Hourdin, F. Forget
12 guez 3
13 guez 157 ! Sch\'ema d'advection "pseudo-amont".
14 guez 31
15 guez 157 USE dimens_m, ONLY: iim, llm
16     USE paramet_m, ONLY: iip1, iip2, ijp1llm, ip1jm, ip1jmp1
17     use vlx_m, only: vlx
18 guez 3
19 guez 157 REAL, intent(inout):: q(ip1jmp1, llm)
20 guez 3
21 guez 157 REAL, intent(in):: pente_max
22     ! facteur de limitation des pentes, 2 en general
23 guez 3
24 guez 157 real, intent(in):: masse(ip1jmp1, llm)
25     REAL, intent(in):: w(ip1jmp1, llm) ! flux de masse
26 guez 3
27 guez 157 REAL, intent(in):: pbaru( ip1jmp1, llm ), pbarv( ip1jm, llm)
28     ! flux de masse en u, v
29 guez 3
30 guez 157 real, intent(in):: pdt ! pas de temps
31 guez 3
32 guez 157 ! Local:
33 guez 3
34 guez 157 INTEGER ij, l
35     REAL zm(ip1jmp1, llm)
36     REAL mu(ip1jmp1, llm)
37     REAL mv(ip1jm, llm)
38     REAL mw(ip1jmp1, llm+1)
39     REAL zzpbar, zzw
40 guez 31
41 guez 157 !---------------------------------------------------------------
42 guez 3
43 guez 157 zzpbar = 0.5 * pdt
44     zzw = pdt
45     DO l = 1, llm
46     DO ij = iip2, ip1jm
47     mu(ij, l) = pbaru(ij, l) * zzpbar
48     ENDDO
49     DO ij = 1, ip1jm
50     mv(ij, l) = pbarv(ij, l) * zzpbar
51     ENDDO
52     DO ij = 1, ip1jmp1
53     mw(ij, l) = w(ij, l) * zzw
54     ENDDO
55     ENDDO
56 guez 40
57 guez 157 DO ij = 1, ip1jmp1
58     mw(ij, llm+1) = 0.
59     ENDDO
60 guez 40
61 guez 157 zm = masse
62 guez 40
63 guez 157 call vlx(q, pente_max, zm, mu)
64     call vly(q, pente_max, zm, mv)
65     call vlz(q, pente_max, zm, mw)
66     call vly(q, pente_max, zm, mv)
67     call vlx(q, pente_max, zm, mu)
68 guez 40
69 guez 157 DO ij = 1, ip1jm + 1, iip1
70     q(ij + iim, :) = q(ij, :)
71     ENDDO
72    
73     END SUBROUTINE vlsplt
74    
75     end module vlsplt_m

  ViewVC Help
Powered by ViewVC 1.1.21