Line data Source code
1 : module restart_physics
2 :
3 : use shr_kind_mod, only: r8 => shr_kind_r8
4 : use spmd_utils, only: masterproc
5 : use co2_cycle, only: co2_transport
6 : use constituents, only: pcnst
7 :
8 : use radiation, only: radiation_define_restart, radiation_write_restart, &
9 : radiation_read_restart
10 :
11 : use ioFileMod
12 : use cam_abortutils, only: endrun
13 : use camsrfexch, only: cam_in_t, cam_out_t
14 : use cam_logfile, only: iulog
15 : use pio, only: file_desc_t, io_desc_t, var_desc_t, &
16 : pio_double, pio_int, pio_noerr, &
17 : pio_seterrorhandling, pio_bcast_error, &
18 : pio_inq_varid, &
19 : pio_def_var, pio_def_dim, &
20 : pio_put_var, pio_get_var
21 :
22 : implicit none
23 : private
24 : save
25 : !
26 : ! Public interfaces
27 : !
28 : public :: write_restart_physics ! Write the physics restart info out
29 : public :: read_restart_physics ! Read the physics restart info in
30 : public :: init_restart_physics
31 :
32 : !
33 : ! Private data
34 : !
35 :
36 : type(var_desc_t) :: flwds_desc, &
37 : solld_desc, co2prog_desc, co2diag_desc, sols_desc, soll_desc, &
38 : solsd_desc
39 :
40 : type(var_desc_t) :: bcphidry_desc, bcphodry_desc, ocphidry_desc, ocphodry_desc, &
41 : dstdry1_desc, dstdry2_desc, dstdry3_desc, dstdry4_desc
42 :
43 : type(var_desc_t) :: cflx_desc(pcnst)
44 :
45 : type(var_desc_t) :: wsx_desc
46 : type(var_desc_t) :: wsy_desc
47 : type(var_desc_t) :: shf_desc
48 :
49 : CONTAINS
50 2304 : subroutine init_restart_physics ( File, pbuf2d)
51 :
52 : use physics_buffer, only: pbuf_init_restart, physics_buffer_desc
53 : use ppgrid, only: pver, pverp
54 : use chemistry, only: chem_init_restart
55 : use prescribed_ozone, only: init_prescribed_ozone_restart
56 : use prescribed_ghg, only: init_prescribed_ghg_restart
57 : use prescribed_aero, only: init_prescribed_aero_restart
58 : use prescribed_volcaero, only: init_prescribed_volcaero_restart
59 : use cam_grid_support, only: cam_grid_write_attr, cam_grid_id
60 : use cam_grid_support, only: cam_grid_header_info_t
61 : use cam_pio_utils, only: cam_pio_def_dim
62 : use subcol_utils, only: is_subcol_on
63 : use subcol, only: subcol_init_restart
64 :
65 : type(file_desc_t), intent(inout) :: file
66 : type(physics_buffer_desc), pointer :: pbuf2d(:,:)
67 :
68 : integer :: grid_id
69 : integer :: hdimcnt, ierr, i
70 : integer :: dimids(4)
71 1536 : integer, allocatable :: hdimids(:)
72 1536 : type(cam_grid_header_info_t) :: info
73 : character(len=4) :: num
74 :
75 1536 : call pio_seterrorhandling(File, PIO_BCAST_ERROR)
76 : ! Probably should have the grid write this out.
77 1536 : grid_id = cam_grid_id('physgrid')
78 1536 : call cam_grid_write_attr(File, grid_id, info)
79 1536 : hdimcnt = info%num_hdims()
80 :
81 3072 : do i = 1, hdimcnt
82 3072 : dimids(i) = info%get_hdimid(i)
83 : end do
84 4608 : allocate(hdimids(hdimcnt))
85 3072 : hdimids(1:hdimcnt) = dimids(1:hdimcnt)
86 :
87 1536 : call pbuf_init_restart(File, pbuf2d)
88 :
89 1536 : call chem_init_restart(File)
90 :
91 1536 : call init_prescribed_ozone_restart(File)
92 1536 : call init_prescribed_ghg_restart(File)
93 1536 : call init_prescribed_aero_restart(File)
94 1536 : call init_prescribed_volcaero_restart(File)
95 :
96 1536 : ierr = pio_def_var(File, 'FLWDS', pio_double, hdimids, flwds_desc)
97 1536 : ierr = pio_def_var(File, 'SOLS', pio_double, hdimids, sols_desc)
98 1536 : ierr = pio_def_var(File, 'SOLL', pio_double, hdimids, soll_desc)
99 1536 : ierr = pio_def_var(File, 'SOLSD', pio_double, hdimids, solsd_desc)
100 1536 : ierr = pio_def_var(File, 'SOLLD', pio_double, hdimids, solld_desc)
101 :
102 1536 : ierr = pio_def_var(File, 'BCPHIDRY', pio_double, hdimids, bcphidry_desc)
103 1536 : ierr = pio_def_var(File, 'BCPHODRY', pio_double, hdimids, bcphodry_desc)
104 1536 : ierr = pio_def_var(File, 'OCPHIDRY', pio_double, hdimids, ocphidry_desc)
105 1536 : ierr = pio_def_var(File, 'OCPHODRY', pio_double, hdimids, ocphodry_desc)
106 1536 : ierr = pio_def_var(File, 'DSTDRY1', pio_double, hdimids, dstdry1_desc)
107 1536 : ierr = pio_def_var(File, 'DSTDRY2', pio_double, hdimids, dstdry2_desc)
108 1536 : ierr = pio_def_var(File, 'DSTDRY3', pio_double, hdimids, dstdry3_desc)
109 1536 : ierr = pio_def_var(File, 'DSTDRY4', pio_double, hdimids, dstdry4_desc)
110 :
111 1536 : if(co2_transport()) then
112 0 : ierr = pio_def_var(File, 'CO2PROG', pio_double, hdimids, co2prog_desc)
113 0 : ierr = pio_def_var(File, 'CO2DIAG', pio_double, hdimids, co2diag_desc)
114 : end if
115 :
116 : ! cam_import variables -- write the constituent surface fluxes as individual 2D arrays
117 : ! rather than as a single variable with a pcnst dimension. Note that the cflx components
118 : ! are only needed for those constituents that are not passed to the coupler. The restart
119 : ! for constituents passed through the coupler are handled by the .rs. restart file. But
120 : ! we don't currently have a mechanism to know whether the constituent is handled by the
121 : ! coupler or not, so we write all of cflx to the CAM restart file.
122 64512 : do i = 1, pcnst
123 62976 : write(num,'(i4.4)') i
124 64512 : ierr = pio_def_var(File, 'CFLX'//num, pio_double, hdimids, cflx_desc(i))
125 : end do
126 :
127 1536 : ierr = pio_def_var(File, 'wsx', pio_double, hdimids, wsx_desc)
128 1536 : ierr = pio_def_var(File, 'wsy', pio_double, hdimids, wsy_desc)
129 1536 : ierr = pio_def_var(File, 'shf', pio_double, hdimids, shf_desc)
130 :
131 1536 : call radiation_define_restart(file)
132 :
133 1536 : if (is_subcol_on()) then
134 0 : call subcol_init_restart(file, hdimids)
135 : end if
136 :
137 1536 : end subroutine init_restart_physics
138 :
139 3072 : subroutine write_restart_physics (File, cam_in, cam_out, pbuf2d)
140 :
141 : !-----------------------------------------------------------------------
142 1536 : use physics_buffer, only: physics_buffer_desc, pbuf_write_restart
143 : use phys_grid, only: phys_decomp
144 :
145 : use ppgrid, only: begchunk, endchunk, pcols, pverp
146 : use chemistry, only: chem_write_restart
147 : use prescribed_ozone, only: write_prescribed_ozone_restart
148 : use prescribed_ghg, only: write_prescribed_ghg_restart
149 : use prescribed_aero, only: write_prescribed_aero_restart
150 : use prescribed_volcaero, only: write_prescribed_volcaero_restart
151 :
152 : use cam_history_support, only: fillvalue
153 : use spmd_utils, only: iam
154 : use cam_grid_support, only: cam_grid_write_dist_array, cam_grid_id
155 : use cam_grid_support, only: cam_grid_get_decomp, cam_grid_dimensions
156 : use cam_grid_support, only: cam_grid_write_var
157 : use pio, only: pio_write_darray
158 : use subcol_utils, only: is_subcol_on
159 : use subcol, only: subcol_write_restart
160 : !
161 : ! Input arguments
162 : !
163 : type(file_desc_t), intent(inout) :: File
164 : type(cam_in_t), intent(in) :: cam_in(begchunk:endchunk)
165 : type(cam_out_t), intent(in) :: cam_out(begchunk:endchunk)
166 : type(physics_buffer_desc), pointer :: pbuf2d(:,:)
167 : !
168 : ! Local workspace
169 : !
170 : type(io_desc_t), pointer :: iodesc
171 3072 : real(r8):: tmpfield(pcols, begchunk:endchunk)
172 : integer :: i, m ! loop index
173 : integer :: ncol ! number of vertical columns
174 : integer :: ierr
175 : integer :: physgrid
176 : integer :: dims(3), gdims(3)
177 : integer :: nhdims
178 : !-----------------------------------------------------------------------
179 :
180 : ! Write grid vars
181 1536 : call cam_grid_write_var(File, phys_decomp)
182 :
183 : ! Physics buffer
184 1536 : if (is_subcol_on()) then
185 0 : call subcol_write_restart(File)
186 : end if
187 :
188 1536 : call pbuf_write_restart(File, pbuf2d)
189 :
190 1536 : physgrid = cam_grid_id('physgrid')
191 1536 : call cam_grid_dimensions(physgrid, gdims(1:2), nhdims)
192 :
193 : ! data for chemistry
194 1536 : call chem_write_restart(File)
195 :
196 1536 : call write_prescribed_ozone_restart(File)
197 1536 : call write_prescribed_ghg_restart(File)
198 1536 : call write_prescribed_aero_restart(File)
199 1536 : call write_prescribed_volcaero_restart(File)
200 :
201 : ! cam_in/out variables
202 : ! This is a group of surface variables so can reuse dims
203 1536 : dims(1) = pcols
204 1536 : dims(2) = endchunk - begchunk + 1
205 0 : call cam_grid_get_decomp(physgrid, dims(1:2), gdims(1:nhdims), &
206 1536 : pio_double, iodesc)
207 :
208 7728 : do i = begchunk, endchunk
209 6192 : ncol = cam_out(i)%ncol
210 103392 : tmpfield(:ncol, i) = cam_out(i)%flwds(:ncol)
211 : ! Only have to do this once (cam_in/out vars all same shape)
212 7728 : if (ncol < pcols) then
213 3408 : tmpfield(ncol+1:, i) = fillvalue
214 : end if
215 : end do
216 1536 : call pio_write_darray(File, flwds_desc, iodesc, tmpfield, ierr)
217 :
218 7728 : do i = begchunk, endchunk
219 6192 : ncol = cam_out(i)%ncol
220 104928 : tmpfield(:ncol, i) = cam_out(i)%sols(:ncol)
221 : end do
222 1536 : call pio_write_darray(File, sols_desc, iodesc, tmpfield, ierr)
223 :
224 7728 : do i = begchunk, endchunk
225 6192 : ncol = cam_out(i)%ncol
226 104928 : tmpfield(:ncol, i) = cam_out(i)%soll(:ncol)
227 : end do
228 1536 : call pio_write_darray(File, soll_desc, iodesc, tmpfield, ierr)
229 :
230 7728 : do i = begchunk, endchunk
231 6192 : ncol = cam_out(i)%ncol
232 104928 : tmpfield(:ncol, i) = cam_out(i)%solsd(:ncol)
233 : end do
234 1536 : call pio_write_darray(File, solsd_desc, iodesc, tmpfield, ierr)
235 :
236 7728 : do i = begchunk, endchunk
237 6192 : ncol = cam_out(i)%ncol
238 104928 : tmpfield(:ncol, i) = cam_out(i)%solld(:ncol)
239 : end do
240 1536 : call pio_write_darray(File, solld_desc, iodesc, tmpfield, ierr)
241 :
242 7728 : do i = begchunk, endchunk
243 6192 : ncol = cam_out(i)%ncol
244 104928 : tmpfield(:ncol, i) = cam_out(i)%bcphidry(:ncol)
245 : end do
246 1536 : call pio_write_darray(File, bcphidry_desc, iodesc, tmpfield, ierr)
247 :
248 7728 : do i = begchunk, endchunk
249 6192 : ncol = cam_out(i)%ncol
250 104928 : tmpfield(:ncol, i) = cam_out(i)%bcphodry(:ncol)
251 : end do
252 1536 : call pio_write_darray(File, bcphodry_desc, iodesc, tmpfield, ierr)
253 :
254 7728 : do i = begchunk, endchunk
255 6192 : ncol = cam_out(i)%ncol
256 104928 : tmpfield(:ncol, i) = cam_out(i)%ocphidry(:ncol)
257 : end do
258 1536 : call pio_write_darray(File, ocphidry_desc, iodesc, tmpfield, ierr)
259 :
260 7728 : do i = begchunk, endchunk
261 6192 : ncol = cam_out(i)%ncol
262 104928 : tmpfield(:ncol, i) = cam_out(i)%ocphodry(:ncol)
263 : end do
264 1536 : call pio_write_darray(File, ocphodry_desc, iodesc, tmpfield, ierr)
265 :
266 7728 : do i = begchunk, endchunk
267 6192 : ncol = cam_out(i)%ncol
268 104928 : tmpfield(:ncol, i) = cam_out(i)%dstdry1(:ncol)
269 : end do
270 1536 : call pio_write_darray(File, dstdry1_desc, iodesc, tmpfield, ierr)
271 :
272 7728 : do i = begchunk, endchunk
273 6192 : ncol = cam_out(i)%ncol
274 104928 : tmpfield(:ncol, i) = cam_out(i)%dstdry2(:ncol)
275 : end do
276 1536 : call pio_write_darray(File, dstdry2_desc, iodesc, tmpfield, ierr)
277 :
278 7728 : do i = begchunk, endchunk
279 6192 : ncol = cam_out(i)%ncol
280 104928 : tmpfield(:ncol, i) = cam_out(i)%dstdry3(:ncol)
281 : end do
282 1536 : call pio_write_darray(File, dstdry3_desc, iodesc, tmpfield, ierr)
283 :
284 7728 : do i = begchunk, endchunk
285 6192 : ncol = cam_out(i)%ncol
286 104928 : tmpfield(:ncol, i) = cam_out(i)%dstdry4(:ncol)
287 : end do
288 1536 : call pio_write_darray(File, dstdry4_desc, iodesc, tmpfield, ierr)
289 :
290 1536 : if (co2_transport()) then
291 0 : do i = begchunk, endchunk
292 0 : ncol = cam_out(i)%ncol
293 0 : tmpfield(:ncol, i) = cam_out(i)%co2prog(:ncol)
294 : end do
295 0 : call pio_write_darray(File, co2prog_desc, iodesc, tmpfield, ierr)
296 :
297 0 : do i = begchunk, endchunk
298 0 : ncol = cam_out(i)%ncol
299 0 : tmpfield(:ncol, i) = cam_out(i)%co2diag(:ncol)
300 : end do
301 0 : call pio_write_darray(File, co2diag_desc, iodesc, tmpfield, ierr)
302 : end if
303 :
304 : ! cam_in components
305 64512 : do m = 1, pcnst
306 316848 : do i = begchunk, endchunk
307 253872 : ncol = cam_in(i)%ncol
308 4302048 : tmpfield(:ncol, i) = cam_in(i)%cflx(:ncol, m)
309 : end do
310 64512 : call pio_write_darray(File, cflx_desc(m), iodesc, tmpfield, ierr)
311 : end do
312 :
313 7728 : do i = begchunk, endchunk
314 6192 : ncol = cam_in(i)%ncol
315 104928 : tmpfield(:ncol,i) = cam_in(i)%wsx(:ncol)
316 : end do
317 1536 : call pio_write_darray(File, wsx_desc, iodesc, tmpfield, ierr)
318 :
319 7728 : do i = begchunk, endchunk
320 6192 : ncol = cam_in(i)%ncol
321 104928 : tmpfield(:ncol,i) = cam_in(i)%wsy(:ncol)
322 : end do
323 1536 : call pio_write_darray(File, wsy_desc, iodesc, tmpfield, ierr)
324 :
325 7728 : do i = begchunk, endchunk
326 6192 : ncol = cam_in(i)%ncol
327 104928 : tmpfield(:ncol,i) = cam_in(i)%shf(:ncol)
328 : end do
329 1536 : call pio_write_darray(File, shf_desc, iodesc, tmpfield, ierr)
330 :
331 1536 : call radiation_write_restart(file)
332 :
333 1536 : end subroutine write_restart_physics
334 :
335 : !#######################################################################
336 :
337 768 : subroutine read_restart_physics(File, cam_in, cam_out, pbuf2d)
338 :
339 : !-----------------------------------------------------------------------
340 1536 : use physics_buffer, only: physics_buffer_desc, pbuf_read_restart
341 :
342 : use ppgrid, only: begchunk, endchunk, pcols, pver, pverp
343 : use chemistry, only: chem_read_restart
344 : use cam_grid_support, only: cam_grid_read_dist_array, cam_grid_id
345 : use cam_grid_support, only: cam_grid_get_decomp, cam_grid_dimensions
346 : use cam_history_support, only: fillvalue
347 :
348 : use prescribed_ozone, only: read_prescribed_ozone_restart
349 : use prescribed_ghg, only: read_prescribed_ghg_restart
350 : use prescribed_aero, only: read_prescribed_aero_restart
351 : use prescribed_volcaero, only: read_prescribed_volcaero_restart
352 : use subcol_utils, only: is_subcol_on
353 : use subcol, only: subcol_read_restart
354 : use pio, only: pio_read_darray
355 : !
356 : ! Arguments
357 : !
358 : type(file_desc_t), intent(inout) :: File
359 : type(cam_in_t), pointer :: cam_in(:)
360 : type(cam_out_t), pointer :: cam_out(:)
361 : type(physics_buffer_desc), pointer :: pbuf2d(:,:)
362 : !
363 : ! Local workspace
364 : !
365 768 : real(r8), allocatable :: tmpfield2(:,:)
366 : integer :: i, c, m ! loop index
367 : integer :: ierr ! I/O status
368 : type(io_desc_t), pointer :: iodesc
369 : type(var_desc_t) :: vardesc
370 : integer :: csize, vsize
371 : character(len=4) :: num
372 : integer :: dims(3), gdims(3), nhdims
373 : integer :: err_handling
374 : integer :: physgrid
375 : !-----------------------------------------------------------------------
376 :
377 : ! subcol_read_restart must be called before pbuf_read_restart
378 768 : if (is_subcol_on()) then
379 0 : call subcol_read_restart(File)
380 : end if
381 :
382 768 : call pbuf_read_restart(File, pbuf2d)
383 :
384 768 : csize=endchunk-begchunk+1
385 768 : dims(1) = pcols
386 768 : dims(2) = csize
387 :
388 768 : physgrid = cam_grid_id('physgrid')
389 :
390 768 : call cam_grid_dimensions(physgrid, gdims(1:2))
391 :
392 768 : if (gdims(2) == 1) then
393 : nhdims = 1
394 : else
395 0 : nhdims = 2
396 : end if
397 0 : call cam_grid_get_decomp(physgrid, dims(1:2), gdims(1:nhdims), pio_double, &
398 768 : iodesc)
399 :
400 : ! data for chemistry
401 768 : call chem_read_restart(File)
402 :
403 768 : call read_prescribed_ozone_restart(File)
404 768 : call read_prescribed_ghg_restart(File)
405 768 : call read_prescribed_aero_restart(File)
406 768 : call read_prescribed_volcaero_restart(File)
407 :
408 2304 : allocate(tmpfield2(pcols, begchunk:endchunk))
409 53400 : tmpfield2 = fillvalue
410 :
411 768 : ierr = pio_inq_varid(File, 'FLWDS', vardesc)
412 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
413 3864 : do c=begchunk,endchunk
414 53400 : do i=1,pcols
415 52632 : cam_out(c)%flwds(i) = tmpfield2(i, c)
416 : end do
417 : end do
418 :
419 768 : ierr = pio_inq_varid(File, 'SOLS', vardesc)
420 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
421 3864 : do c=begchunk,endchunk
422 53400 : do i=1,pcols
423 52632 : cam_out(c)%sols(i) = tmpfield2(i, c)
424 : end do
425 : end do
426 :
427 768 : ierr = pio_inq_varid(File, 'SOLL', vardesc)
428 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
429 3864 : do c=begchunk,endchunk
430 53400 : do i=1,pcols
431 52632 : cam_out(c)%soll(i) = tmpfield2(i, c)
432 : end do
433 : end do
434 :
435 768 : ierr = pio_inq_varid(File, 'SOLSD', vardesc)
436 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
437 3864 : do c=begchunk,endchunk
438 53400 : do i=1,pcols
439 52632 : cam_out(c)%solsd(i) = tmpfield2(i, c)
440 : end do
441 : end do
442 :
443 768 : ierr = pio_inq_varid(File, 'SOLLD', vardesc)
444 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
445 3864 : do c=begchunk,endchunk
446 53400 : do i=1,pcols
447 52632 : cam_out(c)%solld(i) = tmpfield2(i, c)
448 : end do
449 : end do
450 :
451 768 : ierr = pio_inq_varid(File, 'BCPHIDRY', vardesc)
452 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
453 3864 : do c=begchunk,endchunk
454 53400 : do i=1,pcols
455 52632 : cam_out(c)%bcphidry(i) = tmpfield2(i, c)
456 : end do
457 : end do
458 :
459 768 : ierr = pio_inq_varid(File, 'BCPHODRY', vardesc)
460 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
461 3864 : do c=begchunk,endchunk
462 53400 : do i=1,pcols
463 52632 : cam_out(c)%bcphodry(i) = tmpfield2(i, c)
464 : end do
465 : end do
466 :
467 768 : ierr = pio_inq_varid(File, 'OCPHIDRY', vardesc)
468 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
469 3864 : do c=begchunk,endchunk
470 53400 : do i=1,pcols
471 52632 : cam_out(c)%ocphidry(i) = tmpfield2(i, c)
472 : end do
473 : end do
474 :
475 768 : ierr = pio_inq_varid(File, 'OCPHODRY', vardesc)
476 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
477 3864 : do c=begchunk,endchunk
478 53400 : do i=1,pcols
479 52632 : cam_out(c)%ocphodry(i) = tmpfield2(i, c)
480 : end do
481 : end do
482 :
483 768 : ierr = pio_inq_varid(File, 'DSTDRY1', vardesc)
484 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
485 3864 : do c=begchunk,endchunk
486 53400 : do i=1,pcols
487 52632 : cam_out(c)%dstdry1(i) = tmpfield2(i, c)
488 : end do
489 : end do
490 :
491 768 : ierr = pio_inq_varid(File, 'DSTDRY2', vardesc)
492 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
493 3864 : do c=begchunk,endchunk
494 53400 : do i=1,pcols
495 52632 : cam_out(c)%dstdry2(i) = tmpfield2(i, c)
496 : end do
497 : end do
498 :
499 768 : ierr = pio_inq_varid(File, 'DSTDRY3', vardesc)
500 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
501 3864 : do c=begchunk,endchunk
502 53400 : do i=1,pcols
503 52632 : cam_out(c)%dstdry3(i) = tmpfield2(i, c)
504 : end do
505 : end do
506 :
507 768 : ierr = pio_inq_varid(File, 'DSTDRY4', vardesc)
508 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
509 3864 : do c=begchunk,endchunk
510 53400 : do i=1,pcols
511 52632 : cam_out(c)%dstdry4(i) = tmpfield2(i, c)
512 : end do
513 : end do
514 :
515 768 : if (co2_transport()) then
516 0 : ierr = pio_inq_varid(File, 'CO2PROG', vardesc)
517 0 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
518 0 : do c=begchunk,endchunk
519 0 : do i=1,pcols
520 0 : cam_out(c)%co2prog(i) = tmpfield2(i, c)
521 : end do
522 : end do
523 :
524 0 : ierr = pio_inq_varid(File, 'CO2DIAG', vardesc)
525 0 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
526 0 : do c=begchunk,endchunk
527 0 : do i=1,pcols
528 0 : cam_out(c)%co2diag(i) = tmpfield2(i, c)
529 : end do
530 : end do
531 : end if
532 :
533 : ! Reading the CFLX* components from the restart is optional for
534 : ! backwards compatibility. These fields were not needed for an
535 : ! exact restart until the UNICON scheme was added. More generally,
536 : ! these components are only needed if they are not handled by the
537 : ! coupling layer restart (the ".rs." file), and if the values are
538 : ! used in the tphysbc physics before the tphysac code has a chance
539 : ! to update the values that are coming from boundary datasets.
540 32256 : do m = 1, pcnst
541 :
542 31488 : write(num,'(i4.4)') m
543 :
544 31488 : call pio_seterrorhandling(File, PIO_BCAST_ERROR, err_handling)
545 31488 : ierr = pio_inq_varid(File, 'CFLX'//num, vardesc)
546 31488 : call pio_seterrorhandling(File, err_handling)
547 :
548 32256 : if (ierr == PIO_NOERR) then ! CFLX variable found on restart file
549 31488 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
550 158424 : do c= begchunk, endchunk
551 2189400 : do i = 1, pcols
552 2157912 : cam_in(c)%cflx(i,m) = tmpfield2(i, c)
553 : end do
554 : end do
555 : end if
556 :
557 : end do
558 :
559 768 : call pio_seterrorhandling(File, PIO_BCAST_ERROR, err_handling)
560 768 : ierr = pio_inq_varid(File, 'wsx', vardesc)
561 768 : if (ierr == PIO_NOERR) then ! variable found on restart file
562 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
563 3864 : do c= begchunk, endchunk
564 53400 : do i = 1, pcols
565 52632 : cam_in(c)%wsx(i) = tmpfield2(i, c)
566 : end do
567 : end do
568 : end if
569 768 : ierr = pio_inq_varid(File, 'wsy', vardesc)
570 768 : if (ierr == PIO_NOERR) then ! variable found on restart file
571 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
572 3864 : do c= begchunk, endchunk
573 53400 : do i = 1, pcols
574 52632 : cam_in(c)%wsy(i) = tmpfield2(i, c)
575 : end do
576 : end do
577 : end if
578 768 : ierr = pio_inq_varid(File, 'shf', vardesc)
579 768 : if (ierr == PIO_NOERR) then ! variable found on restart file
580 768 : call pio_read_darray(File, vardesc, iodesc, tmpfield2, ierr)
581 3864 : do c= begchunk, endchunk
582 53400 : do i = 1, pcols
583 52632 : cam_in(c)%shf(i) = tmpfield2(i, c)
584 : end do
585 : end do
586 : endif
587 768 : call pio_seterrorhandling(File, err_handling)
588 :
589 768 : deallocate(tmpfield2)
590 :
591 768 : call radiation_read_restart(file)
592 :
593 10752 : end subroutine read_restart_physics
594 :
595 : end module restart_physics
|