/[lmdze]/trunk/dyn3d/dynredem1.f
ViewVC logotype

Annotation of /trunk/dyn3d/dynredem1.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
Original Path: trunk/Sources/dyn3d/dynredem1.f
File size: 2561 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 27 module dynredem1_m
2 guez 3
3 guez 27 IMPLICIT NONE
4 guez 3
5 guez 27 contains
6 guez 3
7 guez 157 SUBROUTINE dynredem1(vcov, ucov, teta, q, masse, ps, itau)
8 guez 3
9 guez 130 ! From dyn3d/dynredem.F, version 1.2, 2004/06/22 11:45:30
10 guez 157 ! Ecriture du fichier de red\'emarrage au format NetCDF
11 guez 3
12 guez 67 USE dimens_m, ONLY: iim, jjm, llm, nqmx
13 guez 157 use dynredem0_m, only: ncid
14 guez 67 USE iniadvtrac_m, ONLY: tname
15 guez 27 use netcdf, only: nf90_write
16     use netcdf95, only: nf95_close, nf95_inq_varid, nf95_open, nf95_put_var
17 guez 67 use nr_util, only: assert
18 guez 3
19 guez 73 REAL, INTENT(IN):: vcov(:, :, :) ! (iim + 1, jjm, llm)
20     REAL, INTENT(IN):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
21     REAL, INTENT(IN):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
22     REAL, INTENT(IN):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
23     REAL, INTENT(IN):: masse(:, :, :) ! (iim + 1, jjm + 1, llm)
24     REAL, INTENT(IN):: ps(:, :) ! (iim + 1, jjm + 1)
25     INTEGER, INTENT(IN):: itau
26 guez 3
27 guez 157 ! Local:
28     INTEGER varid, iq
29 guez 3
30 guez 27 !---------------------------------------------------------
31 guez 3
32 guez 27 PRINT *, 'Call sequence information: dynredem1'
33 guez 3
34 guez 67 call assert((/size(vcov, 1), size(ucov, 1), size(teta, 1), size(q, 1), &
35     size(masse, 1), size(ps, 1)/) == iim + 1, "dynredem1 iim")
36     call assert((/size(vcov, 2) + 1, size(ucov, 2), size(teta, 2), size(q, 2), &
37     size(masse, 2), size(ps, 2)/) == jjm + 1, "dynredem1 jjm")
38     call assert((/size(vcov, 3), size(ucov, 3), size(teta, 3), size(q, 3), &
39     size(masse, 3)/) == llm, "dynredem1 llm")
40     call assert(size(q, 4) == nqmx, "dynredem1 nqmx")
41    
42 guez 157 ! \'Ecriture/extension de la coordonn\'ee temps
43 guez 62 call nf95_inq_varid(ncid, 'temps', varid)
44 guez 104 call nf95_put_var(ncid, varid, values = 0.)
45 guez 3
46 guez 157 ! R\'ecriture du tableau de contr\^ole, "itaufin" n'est pas d\'efini quand
47 guez 27 ! on passe dans "dynredem0"
48 guez 62 call nf95_inq_varid(ncid, 'controle', varid)
49     call nf95_put_var(ncid, varid, real(itau), start=(/31/))
50 guez 3
51 guez 157 ! \'Ecriture des champs
52 guez 3
53 guez 62 call nf95_inq_varid(ncid, 'ucov', varid)
54     call nf95_put_var(ncid, varid, ucov)
55 guez 3
56 guez 62 call nf95_inq_varid(ncid, 'vcov', varid)
57     call nf95_put_var(ncid, varid, vcov)
58 guez 3
59 guez 62 call nf95_inq_varid(ncid, 'teta', varid)
60     call nf95_put_var(ncid, varid, teta)
61 guez 5
62 guez 27 DO iq = 1, nqmx
63 guez 62 call nf95_inq_varid(ncid, tname(iq), varid)
64     call nf95_put_var(ncid, varid, q(:, :, :, iq))
65 guez 27 END DO
66 guez 5
67 guez 62 call nf95_inq_varid(ncid, 'masse', varid)
68     call nf95_put_var(ncid, varid, masse)
69 guez 5
70 guez 62 call nf95_inq_varid(ncid, 'ps', varid)
71     call nf95_put_var(ncid, varid, ps)
72 guez 27
73 guez 62 call nf95_close(ncid)
74 guez 27
75     END SUBROUTINE dynredem1
76    
77     end module dynredem1_m

  ViewVC Help
Powered by ViewVC 1.1.21