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

Contents of /trunk/dyn3d/gcm.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 157 - (show annotations)
Mon Jul 20 16:01:49 2015 UTC (8 years, 9 months ago) by guez
Original Path: trunk/Sources/dyn3d/gcm.f
File size: 4170 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 PROGRAM gcm
2
3 ! Authors: P. Le Van, L. Fairhead, F. Hourdin
4 ! From "gcm.F", version 1.4, 2006/04/04 15:05:16
5
6 ! General circulation model of LMD. Avec coordonn\'ee verticale
7 ! hybride, avec nouveaux op\'erateurs de dissipation "*" ("gradiv2",
8 ! "divgrad2", "nxgraro2"). Possibilit\'e de choisir le sch\'ema pour
9 ! l'advection de "q", en modifiant "iadv" dans "traceur.def".
10
11 use comconst, only: daysec, dtvr, iniconst
12 use comgeom, only: aire_2d, cu_2d, cv_2d, inigeom
13 use comgeomphy, only: airephy, cuphy, cvphy, rlatd, rlond
14 use conf_gcm_m, only: day_step, iperiod, iecri, iphysiq, nday, periodav, &
15 conf_gcm, iflag_phys
16 use conf_guide_m, only: conf_guide
17 use dimens_m, only: iim, jjm, llm, nqmx
18 use dimphy, only: klon
19 USE disvert_m, ONLY : disvert
20 use dynetat0_m, only: rlatu, rlonv, dynetat0, day_ini
21 use dynredem0_m, only: dynredem0
22 use grid_change, only: dyn_phy, init_dyn_phy
23 use histclo_m, only: histclo
24 use iniadvtrac_m, only: iniadvtrac
25 use inidissip_m, only: inidissip
26 use inifilr_m, only: inifilr
27 use initdynav_m, only: initdynav
28 use inithist_m, only: inithist
29 use init_dynzon_m, only: init_dynzon
30 USE ioconf_calendar_m, only: ioconf_calendar
31 use jumble, only: new_unit
32 use leapfrog_m, only: leapfrog
33 use netcdf95, only: nf95_close
34 use suphec_m, only: suphec
35 use tracstoke, only: istdyn, istphy
36 use unit_nml_m, only: unit_nml
37 use yoethf_m, only: yoethf
38 use createnewfield_m, only: NbField, Ncid
39
40 IMPLICIT NONE
41
42 ! Variables dynamiques :
43 REAL ucov(iim + 1, jjm + 1, llm), vcov(iim + 1, jjm, llm) ! vent covariant
44 REAL teta(iim + 1, jjm + 1, llm) ! temp\'erature potentielle
45 REAL q(iim + 1, jjm + 1, llm, nqmx) ! champs advect\'es
46 REAL ps(iim + 1, jjm + 1) ! pression au sol (Pa)
47 REAL masse(iim + 1, jjm + 1, llm) ! masse d'air
48 REAL phis(iim + 1, jjm + 1) ! g\'eopotentiel au sol
49
50 ! Calendrier :
51 LOGICAL:: true_calendar = .false. ! default value
52
53 logical mask_v(iim + 1, jjm)
54 ! (mask for points in the "v" grid, first index is for longitude,
55 ! second index is for latitude)
56
57 integer i
58
59 namelist /main_nml/true_calendar
60
61 !------------------------------------------------------------
62
63 call new_unit(unit_nml)
64 open(unit_nml, file="used_namelists.txt", status="replace", action="write")
65
66 CALL conf_gcm
67
68 print *, "Enter namelist 'main_nml'."
69 read (unit=*, nml=main_nml)
70 write(unit_nml, nml=main_nml)
71
72 ! Choix du calendrier :
73 if (true_calendar) then
74 call ioconf_calendar('gregorian')
75 else
76 call ioconf_calendar('360d')
77 endif
78
79 call iniadvtrac
80 CALL iniconst
81 CALL dynetat0(vcov, ucov, teta, q, masse, ps, phis)
82 CALL disvert
83 CALL inigeom ! initialisation de la g\'eometrie
84 CALL inifilr ! initialisation du filtre
85 CALL inidissip
86 call init_dyn_phy
87
88 ! Initialisation de la physique :
89 IF (iflag_phys == 1) THEN
90 rlatd(1)=rlatu(1)
91 rlatd(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.)
92 rlatd(klon)= rlatu(jjm + 1)
93
94 rlond(1)=0.
95 rlond(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.)
96 rlond(klon)= 0.
97
98 cuphy = pack(cu_2d, dyn_phy)
99
100 ! Construct a mask for points in the "v" grid:
101 mask_v = .true.
102 mask_v(2:, 1) = .false.
103 mask_v(iim + 1, 2:) = .false.
104
105 cvphy(:klon - 1) = pack(cv_2d, mask_v)
106 cvphy(klon) = cv_2d(1, jjm)
107 ! (that value of "cv_2d" is used twice in "cvphy")
108
109 airephy = pack(aire_2d, dyn_phy)
110 CALL suphec
111 call yoethf
112 ENDIF
113
114 ! Initialisation des entr\'ees-sorties :
115 CALL dynredem0(day_ini + nday, phis)
116 CALL inithist(dtvr, nqmx, t_ops = iecri * daysec, t_wrt = iecri * daysec)
117 CALL initdynav(dtvr, nqmx, t_ops = iperiod * dtvr, t_wrt = periodav * daysec)
118 call init_dynzon(dt_app = dtvr * iperiod)
119
120 ! Choix des fr\'equences de stockage pour le hors-ligne :
121 istdyn = day_step / 4 ! stockage toutes les 6 h = 1 jour / 4
122 istphy = istdyn / iphysiq
123
124 CALL conf_guide
125 CALL leapfrog(ucov, vcov, teta, ps, masse, phis, q)
126
127 close(unit_nml)
128 call histclo
129
130 do i = 1, nbfield
131 call nf95_close(Ncid(i))
132 end do
133
134 print *, 'Simulation finished'
135 print *, 'Everything is cool'
136
137 END PROGRAM gcm

  ViewVC Help
Powered by ViewVC 1.1.21