SCALE-RM
mod_atmos_phy_rd_vars.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
12 !-------------------------------------------------------------------------------
13 #include "inc_openmp.h"
15  !-----------------------------------------------------------------------------
16  !
17  !++ used modules
18  !
19  use scale_precision
20  use scale_stdio
21  use scale_prof
23  use scale_tracer
24  !-----------------------------------------------------------------------------
25  implicit none
26  private
27  !-----------------------------------------------------------------------------
28  !
29  !++ Public procedure
30  !
31  public :: atmos_phy_rd_vars_setup
36 
42 
43  !-----------------------------------------------------------------------------
44  !
45  !++ Public parameters & variables
46  !
47  logical, public :: atmos_phy_rd_restart_output = .false.
48 
49  character(len=H_LONG), public :: atmos_phy_rd_restart_in_basename = ''
50  character(len=H_LONG), public :: atmos_phy_rd_restart_out_basename = ''
51  character(len=H_MID), public :: atmos_phy_rd_restart_out_title = 'ATMOS_PHY_RD restart'
52  character(len=H_MID), public :: atmos_phy_rd_restart_out_dtype = 'DEFAULT'
53 
54  real(RP), public, allocatable :: atmos_phy_rd_rhot_t(:,:,:) ! tendency RHOT [K*kg/m3/s]
55 
56  real(RP), public, allocatable :: atmos_phy_rd_sflx_lw_up (:,:) ! surface upward longwave flux [J/m2/s]
57  real(RP), public, allocatable :: atmos_phy_rd_sflx_lw_dn (:,:) ! surface downward longwave flux [J/m2/s]
58  real(RP), public, allocatable :: atmos_phy_rd_sflx_sw_up (:,:) ! surface upward shortwave flux [J/m2/s]
59  real(RP), public, allocatable :: atmos_phy_rd_sflx_sw_dn (:,:) ! surface downward shortwave flux [J/m2/s]
60 
61  real(RP), public, allocatable :: atmos_phy_rd_toaflx_lw_up(:,:) ! TOA upward longwave flux [J/m2/s]
62  real(RP), public, allocatable :: atmos_phy_rd_toaflx_lw_dn(:,:) ! TOA downward longwave flux [J/m2/s]
63  real(RP), public, allocatable :: atmos_phy_rd_toaflx_sw_up(:,:) ! TOA upward shortwave flux [J/m2/s]
64  real(RP), public, allocatable :: atmos_phy_rd_toaflx_sw_dn(:,:) ! TOA downward shortwave flux [J/m2/s]
65 
66  real(RP), public, allocatable :: atmos_phy_rd_sflx_downall(:,:,:,:) ! surface downward flux (LW/SW,direct/diffuse) [J/m2/s]
67 
68  real(RP), public, allocatable :: atmos_phy_rd_solins (:,:) ! solar insolation flux [J/m2/s]
69  real(RP), public, allocatable :: atmos_phy_rd_cossza (:,:) ! cos(solar zenith angle) [0-1]
70 
71  !-----------------------------------------------------------------------------
72  !
73  !++ Private procedure
74  !
75  !-----------------------------------------------------------------------------
76  !
77  !++ Private parameters & variables
78  !
79  integer, private, parameter :: vmax = 12
80  integer, private, parameter :: i_sflx_lw_up = 1
81  integer, private, parameter :: i_sflx_lw_dn = 2
82  integer, private, parameter :: i_sflx_sw_up = 3
83  integer, private, parameter :: i_sflx_sw_dn = 4
84  integer, private, parameter :: i_toaflx_lw_up = 5
85  integer, private, parameter :: i_toaflx_lw_dn = 6
86  integer, private, parameter :: i_toaflx_sw_up = 7
87  integer, private, parameter :: i_toaflx_sw_dn = 8
88  integer, private, parameter :: i_sflx_lw_dir = 9
89  integer, private, parameter :: i_sflx_lw_dif = 10
90  integer, private, parameter :: i_sflx_sw_dir = 11
91  integer, private, parameter :: i_sflx_sw_dif = 12
92 
93  character(len=H_SHORT), private :: var_name(vmax)
94  character(len=H_MID), private :: var_desc(vmax)
95  character(len=H_SHORT), private :: var_unit(vmax)
96  integer, private :: var_id(vmax)
97  integer, private :: restart_fid = -1 ! file ID
98 
99  data var_name / 'SFLX_LW_up', &
100  'SFLX_LW_dn', &
101  'SFLX_SW_up', &
102  'SFLX_SW_dn', &
103  'TOAFLX_LW_up', &
104  'TOAFLX_LW_dn', &
105  'TOAFLX_SW_up', &
106  'TOAFLX_SW_dn', &
107  'SFLX_LW_dir', &
108  'SFLX_LW_dif', &
109  'SFLX_SW_dir', &
110  'SFLX_SW_dif' /
111  data var_desc / 'surface upward longwave flux', &
112  'surface downward longwave flux', &
113  'surface upward shortwave flux', &
114  'surface downward shortwave flux', &
115  'TOA upward longwave flux', &
116  'TOA downward longwave flux', &
117  'TOA upward shortwave flux', &
118  'TOA downward shortwave flux', &
119  'sfc. down. longwave flux direct', &
120  'sfc. down. longwave flux diffuse', &
121  'sfc. down. shortwave flux direct', &
122  'sfc. down. shortwave flux diffuse' /
123  data var_unit / 'W/m2', &
124  'W/m2', &
125  'W/m2', &
126  'W/m2', &
127  'W/m2', &
128  'W/m2', &
129  'W/m2', &
130  'W/m2', &
131  'W/m2', &
132  'W/m2', &
133  'W/m2', &
134  'W/m2' /
135 
136  !-----------------------------------------------------------------------------
137 contains
138  !-----------------------------------------------------------------------------
140  subroutine atmos_phy_rd_vars_setup
141  use scale_process, only: &
143  use scale_const, only: &
144  undef => const_undef
145  implicit none
146 
147  namelist / param_atmos_phy_rd_vars / &
153 
154  integer :: ierr
155  integer :: iv
156  !---------------------------------------------------------------------------
157 
158  if( io_l ) write(io_fid_log,*)
159  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[ATMOS PHY_RD] / Origin[SCALE-RM]'
160 
161  allocate( atmos_phy_rd_rhot_t(ka,ia,ja) )
162  atmos_phy_rd_rhot_t(:,:,:) = undef
163 
164  allocate( atmos_phy_rd_sflx_lw_up(ia,ja) )
165  allocate( atmos_phy_rd_sflx_lw_dn(ia,ja) )
166  allocate( atmos_phy_rd_sflx_sw_up(ia,ja) )
167  allocate( atmos_phy_rd_sflx_sw_dn(ia,ja) )
168  allocate( atmos_phy_rd_toaflx_lw_up(ia,ja) )
169  allocate( atmos_phy_rd_toaflx_lw_dn(ia,ja) )
170  allocate( atmos_phy_rd_toaflx_sw_up(ia,ja) )
171  allocate( atmos_phy_rd_toaflx_sw_dn(ia,ja) )
172  atmos_phy_rd_sflx_lw_up(:,:) = undef
173  atmos_phy_rd_sflx_lw_dn(:,:) = undef
174  atmos_phy_rd_sflx_sw_up(:,:) = undef
175  atmos_phy_rd_sflx_sw_dn(:,:) = undef
176  atmos_phy_rd_toaflx_lw_up(:,:) = undef
177  atmos_phy_rd_toaflx_lw_dn(:,:) = undef
178  atmos_phy_rd_toaflx_sw_up(:,:) = undef
179  atmos_phy_rd_toaflx_sw_dn(:,:) = undef
180 
181  allocate( atmos_phy_rd_sflx_downall(ia,ja,2,2) )
182  atmos_phy_rd_sflx_downall(:,:,:,:) = undef
183 
184  allocate( atmos_phy_rd_solins(ia,ja) )
185  allocate( atmos_phy_rd_cossza(ia,ja) )
186  atmos_phy_rd_solins(:,:) = undef
187  atmos_phy_rd_cossza(:,:) = undef
188 
189  !--- read namelist
190  rewind(io_fid_conf)
191  read(io_fid_conf,nml=param_atmos_phy_rd_vars,iostat=ierr)
192  if( ierr < 0 ) then !--- missing
193  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
194  elseif( ierr > 0 ) then !--- fatal error
195  write(*,*) 'xxx Not appropriate names in namelist PARAM_ATMOS_PHY_RD_VARS. Check!'
196  call prc_mpistop
197  endif
198  if( io_lnml ) write(io_fid_log,nml=param_atmos_phy_rd_vars)
199 
200  if( io_l ) write(io_fid_log,*)
201  if( io_l ) write(io_fid_log,*) '*** [ATMOS_PHY_RD] prognostic/diagnostic variables'
202  if( io_l ) write(io_fid_log,'(1x,A,A15,A,A32,3(A))') &
203  '*** |','VARNAME ','|', 'DESCRIPTION ','[', 'UNIT ',']'
204  do iv = 1, vmax
205  if( io_l ) write(io_fid_log,'(1x,A,i3,A,A15,A,A32,3(A))') &
206  '*** NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
207  enddo
208 
209  if( io_l ) write(io_fid_log,*)
210  if ( atmos_phy_rd_restart_in_basename /= '' ) then
211  if( io_l ) write(io_fid_log,*) '*** Restart input? : ', trim(atmos_phy_rd_restart_in_basename)
212  else
213  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
214  endif
216  .AND. atmos_phy_rd_restart_out_basename /= '' ) then
217  if( io_l ) write(io_fid_log,*) '*** Restart output? : ', trim(atmos_phy_rd_restart_out_basename)
218  else
219  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
221  endif
222 
223  return
224  end subroutine atmos_phy_rd_vars_setup
225 
226  !-----------------------------------------------------------------------------
228  subroutine atmos_phy_rd_vars_fillhalo
229  use scale_comm, only: &
230  comm_vars8, &
231  comm_wait
232  implicit none
233 
234  integer :: n ,iw, id
235  !---------------------------------------------------------------------------
236 
237  call comm_vars8( atmos_phy_rd_sflx_lw_up(:,:), 1 )
238  call comm_vars8( atmos_phy_rd_sflx_lw_dn(:,:), 2 )
239  call comm_vars8( atmos_phy_rd_sflx_sw_up(:,:), 3 )
240  call comm_vars8( atmos_phy_rd_sflx_sw_dn(:,:), 4 )
241  call comm_vars8( atmos_phy_rd_toaflx_lw_up(:,:), 5 )
242  call comm_vars8( atmos_phy_rd_toaflx_lw_dn(:,:), 6 )
243  call comm_vars8( atmos_phy_rd_toaflx_sw_up(:,:), 7 )
244  call comm_vars8( atmos_phy_rd_toaflx_sw_dn(:,:), 8 )
245 
246  n = 8
247  do id = 1, 2 ! direct/diffuse
248  do iw = 1, 2 ! SW/LW
249  n = n + 1
250  call comm_vars8( atmos_phy_rd_sflx_downall(:,:,iw,id), n )
251  enddo
252  enddo
253 
254  call comm_wait ( atmos_phy_rd_sflx_lw_up(:,:), 1 )
255  call comm_wait ( atmos_phy_rd_sflx_lw_dn(:,:), 2 )
256  call comm_wait ( atmos_phy_rd_sflx_sw_up(:,:), 3 )
257  call comm_wait ( atmos_phy_rd_sflx_sw_dn(:,:), 4 )
258  call comm_wait ( atmos_phy_rd_toaflx_lw_up(:,:), 5 )
259  call comm_wait ( atmos_phy_rd_toaflx_lw_dn(:,:), 6 )
260  call comm_wait ( atmos_phy_rd_toaflx_sw_up(:,:), 7 )
261  call comm_wait ( atmos_phy_rd_toaflx_sw_dn(:,:), 8 )
262 
263  n = 8
264  do id = 1, 2 ! direct/diffuse
265  do iw = 1, 2 ! SW/LW
266  n = n + 1
267  call comm_wait ( atmos_phy_rd_sflx_downall(:,:,iw,id), n )
268  enddo
269  enddo
270 
271  return
272  end subroutine atmos_phy_rd_vars_fillhalo
273 
274  !-----------------------------------------------------------------------------
277  use scale_fileio, only: &
278  fileio_read
279  use scale_rm_statistics, only: &
280  stat_total
281  implicit none
282 
283  real(RP) :: total
284  !---------------------------------------------------------------------------
285 
286  if( io_l ) write(io_fid_log,*)
287  if( io_l ) write(io_fid_log,*) '*** Input restart file (ATMOS_PHY_RD) ***'
288 
289  if ( atmos_phy_rd_restart_in_basename /= '' ) then
290  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(atmos_phy_rd_restart_in_basename)
291 
292  call fileio_read( atmos_phy_rd_sflx_lw_up(:,:), & ! [OUT]
293  atmos_phy_rd_restart_in_basename, var_name(1) , 'XY', step=1 ) ! [IN]
294  call fileio_read( atmos_phy_rd_sflx_lw_dn(:,:), & ! [OUT]
295  atmos_phy_rd_restart_in_basename, var_name(2) , 'XY', step=1 ) ! [IN]
296  call fileio_read( atmos_phy_rd_sflx_sw_up(:,:), & ! [OUT]
297  atmos_phy_rd_restart_in_basename, var_name(3) , 'XY', step=1 ) ! [IN]
298  call fileio_read( atmos_phy_rd_sflx_sw_dn(:,:), & ! [OUT]
299  atmos_phy_rd_restart_in_basename, var_name(4) , 'XY', step=1 ) ! [IN]
300  call fileio_read( atmos_phy_rd_toaflx_lw_up(:,:), & ! [OUT]
301  atmos_phy_rd_restart_in_basename, var_name(5) , 'XY', step=1 ) ! [IN]
302  call fileio_read( atmos_phy_rd_toaflx_lw_dn(:,:), & ! [OUT]
303  atmos_phy_rd_restart_in_basename, var_name(6) , 'XY', step=1 ) ! [IN]
304  call fileio_read( atmos_phy_rd_toaflx_sw_up(:,:), & ! [OUT]
305  atmos_phy_rd_restart_in_basename, var_name(7) , 'XY', step=1 ) ! [IN]
306  call fileio_read( atmos_phy_rd_toaflx_sw_dn(:,:), & ! [OUT]
307  atmos_phy_rd_restart_in_basename, var_name(8) , 'XY', step=1 ) ! [IN]
308  call fileio_read( atmos_phy_rd_sflx_downall(:,:,1,1), & ! [OUT]
309  atmos_phy_rd_restart_in_basename, var_name(9) , 'XY', step=1 ) ! [IN]
310  call fileio_read( atmos_phy_rd_sflx_downall(:,:,1,2), & ! [OUT]
311  atmos_phy_rd_restart_in_basename, var_name(10), 'XY', step=1 ) ! [IN]
312  call fileio_read( atmos_phy_rd_sflx_downall(:,:,2,1), & ! [OUT]
313  atmos_phy_rd_restart_in_basename, var_name(11), 'XY', step=1 ) ! [IN]
314  call fileio_read( atmos_phy_rd_sflx_downall(:,:,2,2), & ! [OUT]
315  atmos_phy_rd_restart_in_basename, var_name(12), 'XY', step=1 ) ! [IN]
316 
318 
319  call stat_total( total, atmos_phy_rd_sflx_lw_up(:,:), var_name(1) )
320  call stat_total( total, atmos_phy_rd_sflx_lw_dn(:,:), var_name(2) )
321  call stat_total( total, atmos_phy_rd_sflx_sw_up(:,:), var_name(3) )
322  call stat_total( total, atmos_phy_rd_sflx_sw_dn(:,:), var_name(4) )
323  call stat_total( total, atmos_phy_rd_toaflx_lw_up(:,:), var_name(5) )
324  call stat_total( total, atmos_phy_rd_toaflx_lw_dn(:,:), var_name(6) )
325  call stat_total( total, atmos_phy_rd_toaflx_sw_up(:,:), var_name(7) )
326  call stat_total( total, atmos_phy_rd_toaflx_sw_dn(:,:), var_name(8) )
327  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,1,1), var_name(9) )
328  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,1,2), var_name(10) )
329  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,2,1), var_name(11) )
330  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,2,2), var_name(12) )
331  else
332  if( io_l ) write(io_fid_log,*) '*** restart file for ATMOS_PHY_RD is not specified.'
333  endif
334 
335  return
336  end subroutine atmos_phy_rd_vars_restart_read
337 
338  !-----------------------------------------------------------------------------
341  use scale_time, only: &
343  use scale_fileio, only: &
344  fileio_write
345  use scale_rm_statistics, only: &
346  stat_total
347  implicit none
348 
349  character(len=20) :: timelabel
350  character(len=H_LONG) :: basename
351 
352  real(RP) :: total
353  !---------------------------------------------------------------------------
354 
355  if ( atmos_phy_rd_restart_out_basename /= '' ) then
356 
357  call time_gettimelabel( timelabel )
358  write(basename,'(A,A,A)') trim(atmos_phy_rd_restart_out_basename), '_', trim(timelabel)
359 
360  if( io_l ) write(io_fid_log,*)
361  if( io_l ) write(io_fid_log,*) '*** Output restart file (ATMOS_PHY_RD) ***'
362  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
363 
365 
366  call stat_total( total, atmos_phy_rd_sflx_lw_up(:,:), var_name(1) )
367  call stat_total( total, atmos_phy_rd_sflx_lw_dn(:,:), var_name(2) )
368  call stat_total( total, atmos_phy_rd_sflx_sw_up(:,:), var_name(3) )
369  call stat_total( total, atmos_phy_rd_sflx_sw_dn(:,:), var_name(4) )
370  call stat_total( total, atmos_phy_rd_toaflx_lw_up(:,:), var_name(5) )
371  call stat_total( total, atmos_phy_rd_toaflx_lw_dn(:,:), var_name(6) )
372  call stat_total( total, atmos_phy_rd_toaflx_sw_up(:,:), var_name(7) )
373  call stat_total( total, atmos_phy_rd_toaflx_sw_dn(:,:), var_name(8) )
374  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,1,1), var_name(9) )
375  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,1,2), var_name(10) )
376  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,2,1), var_name(11) )
377  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,2,2), var_name(12) )
378 
379  call fileio_write( atmos_phy_rd_sflx_lw_up(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
380  var_name(1) , var_desc(1) , var_unit(1) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
381  call fileio_write( atmos_phy_rd_sflx_lw_dn(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
382  var_name(2) , var_desc(2) , var_unit(2) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
383  call fileio_write( atmos_phy_rd_sflx_sw_up(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
384  var_name(3) , var_desc(3) , var_unit(3) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
385  call fileio_write( atmos_phy_rd_sflx_sw_dn(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
386  var_name(4) , var_desc(4) , var_unit(4) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
387  call fileio_write( atmos_phy_rd_toaflx_lw_up(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
388  var_name(5) , var_desc(5) , var_unit(5) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
389  call fileio_write( atmos_phy_rd_toaflx_lw_dn(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
390  var_name(6) , var_desc(6) , var_unit(6) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
391  call fileio_write( atmos_phy_rd_toaflx_sw_up(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
392  var_name(7) , var_desc(7) , var_unit(7) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
393  call fileio_write( atmos_phy_rd_toaflx_sw_dn(:,:) , basename, atmos_phy_rd_restart_out_title, & ! [IN]
394  var_name(8) , var_desc(8) , var_unit(8) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
395  call fileio_write( atmos_phy_rd_sflx_downall(:,:,1,1), basename, atmos_phy_rd_restart_out_title, & ! [IN]
396  var_name(9) , var_desc(9) , var_unit(9) , 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
397  call fileio_write( atmos_phy_rd_sflx_downall(:,:,1,2), basename, atmos_phy_rd_restart_out_title, & ! [IN]
398  var_name(10), var_desc(10), var_unit(10), 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
399  call fileio_write( atmos_phy_rd_sflx_downall(:,:,2,1), basename, atmos_phy_rd_restart_out_title, & ! [IN]
400  var_name(11), var_desc(11), var_unit(11), 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
401  call fileio_write( atmos_phy_rd_sflx_downall(:,:,2,2), basename, atmos_phy_rd_restart_out_title, & ! [IN]
402  var_name(12), var_desc(12), var_unit(12), 'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
403 
404 
405  endif
406 
407  return
408  end subroutine atmos_phy_rd_vars_restart_write
409 
410  !-----------------------------------------------------------------------------
412  subroutine atmos_phy_rd_vars_external_in( &
413  init_value_in )
414  implicit none
415 
416  real(RP), intent(in) :: init_value_in
417  !---------------------------------------------------------------------------
418 
419  if( io_l ) write(io_fid_log,*)
420  if( io_l ) write(io_fid_log,*) '*** External Input (PHY_RD) ***'
421 
422  atmos_phy_rd_sflx_lw_up(:,:) = init_value_in
423  atmos_phy_rd_sflx_lw_dn(:,:) = init_value_in
424  atmos_phy_rd_sflx_sw_up(:,:) = init_value_in
425  atmos_phy_rd_sflx_sw_dn(:,:) = init_value_in
426  atmos_phy_rd_toaflx_lw_up(:,:) = init_value_in
427  atmos_phy_rd_toaflx_lw_dn(:,:) = init_value_in
428  atmos_phy_rd_toaflx_sw_up(:,:) = init_value_in
429  atmos_phy_rd_toaflx_sw_dn(:,:) = init_value_in
430  atmos_phy_rd_sflx_downall(:,:,:,:) = init_value_in
431 
432  return
433  end subroutine atmos_phy_rd_vars_external_in
434 
435  !-----------------------------------------------------------------------------
438  use scale_time, only: &
440  use scale_fileio, only: &
442  use scale_rm_statistics, only: &
443  stat_total
444  implicit none
445 
446  character(len=20) :: timelabel
447  character(len=H_LONG) :: basename
448 
449  !---------------------------------------------------------------------------
450 
451  if ( atmos_phy_rd_restart_out_basename /= '' ) then
452 
453  call time_gettimelabel( timelabel )
454  write(basename,'(A,A,A)') trim(atmos_phy_rd_restart_out_basename), '_', trim(timelabel)
455 
456  if( io_l ) write(io_fid_log,*)
457  if( io_l ) write(io_fid_log,*) '*** Output restart file (ATMOS_PHY_RD) ***'
458  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
459 
460  call fileio_create(restart_fid, basename, atmos_phy_rd_restart_out_title, &
462 
463  endif
464 
465  return
466  end subroutine atmos_phy_rd_vars_restart_create
467 
468  !-----------------------------------------------------------------------------
471  use scale_fileio, only: &
473  implicit none
474 
475  if ( restart_fid .NE. -1 ) then
476  call fileio_enddef( restart_fid ) ! [IN]
477  endif
478 
479  return
480  end subroutine atmos_phy_rd_vars_restart_enddef
481 
482  !-----------------------------------------------------------------------------
485  use scale_fileio, only: &
487  implicit none
488 
489  if ( restart_fid .NE. -1 ) then
490  call fileio_close( restart_fid ) ! [IN]
491  restart_fid = -1
492  endif
493 
494  return
495  end subroutine atmos_phy_rd_vars_restart_close
496 
497  !-----------------------------------------------------------------------------
500  use scale_fileio, only: &
502  implicit none
503 
504  character(len=20) :: timelabel
505  character(len=H_LONG) :: basename
506 
507  !---------------------------------------------------------------------------
508 
509  if ( restart_fid .NE. -1 ) then
510 
511  call fileio_def_var( restart_fid, var_id(1), var_name(1) , var_desc(1) , var_unit(1) , &
512  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
513  call fileio_def_var( restart_fid, var_id(2), var_name(2) , var_desc(2) , var_unit(2) , &
514  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
515  call fileio_def_var( restart_fid, var_id(3), var_name(3) , var_desc(3) , var_unit(3) , &
516  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
517  call fileio_def_var( restart_fid, var_id(4), var_name(4) , var_desc(4) , var_unit(4) , &
518  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
519  call fileio_def_var( restart_fid, var_id(5), var_name(5) , var_desc(5) , var_unit(5) , &
520  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
521  call fileio_def_var( restart_fid, var_id(6), var_name(6) , var_desc(6) , var_unit(6) , &
522  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
523  call fileio_def_var( restart_fid, var_id(7), var_name(7) , var_desc(7) , var_unit(7) , &
524  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
525  call fileio_def_var( restart_fid, var_id(8), var_name(8) , var_desc(8) , var_unit(8) , &
526  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
527  call fileio_def_var( restart_fid, var_id(9), var_name(9) , var_desc(9) , var_unit(9) , &
528  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
529  call fileio_def_var( restart_fid, var_id(10), var_name(10), var_desc(10), var_unit(10), &
530  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
531  call fileio_def_var( restart_fid, var_id(11), var_name(11), var_desc(11), var_unit(11), &
532  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
533  call fileio_def_var( restart_fid, var_id(12), var_name(12), var_desc(12), var_unit(12), &
534  'XY', atmos_phy_rd_restart_out_dtype ) ! [IN]
535 
536  endif
537 
538  return
539  end subroutine atmos_phy_rd_vars_restart_def_var
540 
541  !-----------------------------------------------------------------------------
544  use scale_fileio, only: &
545  fileio_write_var
546  use scale_rm_statistics, only: &
547  stat_total
548  implicit none
549 
550  real(RP) :: total
551  !---------------------------------------------------------------------------
552 
553  if ( restart_fid .NE. -1 ) then
554 
556 
557  call stat_total( total, atmos_phy_rd_sflx_lw_up(:,:), var_name(1) )
558  call stat_total( total, atmos_phy_rd_sflx_lw_dn(:,:), var_name(2) )
559  call stat_total( total, atmos_phy_rd_sflx_sw_up(:,:), var_name(3) )
560  call stat_total( total, atmos_phy_rd_sflx_sw_dn(:,:), var_name(4) )
561  call stat_total( total, atmos_phy_rd_toaflx_lw_up(:,:), var_name(5) )
562  call stat_total( total, atmos_phy_rd_toaflx_lw_dn(:,:), var_name(6) )
563  call stat_total( total, atmos_phy_rd_toaflx_sw_up(:,:), var_name(7) )
564  call stat_total( total, atmos_phy_rd_toaflx_sw_dn(:,:), var_name(8) )
565  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,1,1), var_name(9) )
566  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,1,2), var_name(10) )
567  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,2,1), var_name(11) )
568  call stat_total( total, atmos_phy_rd_sflx_downall(:,:,2,2), var_name(12) )
569 
570  call fileio_write_var( restart_fid, var_id(1), atmos_phy_rd_sflx_lw_up(:,:), &
571  var_name(1) , 'XY' ) ! [IN]
572  call fileio_write_var( restart_fid, var_id(2), atmos_phy_rd_sflx_lw_dn(:,:), &
573  var_name(2) , 'XY' ) ! [IN]
574  call fileio_write_var( restart_fid, var_id(3), atmos_phy_rd_sflx_sw_up(:,:), &
575  var_name(3) , 'XY' ) ! [IN]
576  call fileio_write_var( restart_fid, var_id(4), atmos_phy_rd_sflx_sw_dn(:,:), &
577  var_name(4) , 'XY' ) ! [IN]
578  call fileio_write_var( restart_fid, var_id(5), atmos_phy_rd_toaflx_lw_up(:,:), &
579  var_name(5) , 'XY' ) ! [IN]
580  call fileio_write_var( restart_fid, var_id(6), atmos_phy_rd_toaflx_lw_dn(:,:), &
581  var_name(6) , 'XY' ) ! [IN]
582  call fileio_write_var( restart_fid, var_id(7), atmos_phy_rd_toaflx_sw_up(:,:), &
583  var_name(7) , 'XY' ) ! [IN]
584  call fileio_write_var( restart_fid, var_id(8), atmos_phy_rd_toaflx_sw_dn(:,:), &
585  var_name(8) , 'XY' ) ! [IN]
586  call fileio_write_var( restart_fid, var_id(9), atmos_phy_rd_sflx_downall(:,:,1,1), &
587  var_name(9) , 'XY' ) ! [IN]
588  call fileio_write_var( restart_fid, var_id(10), atmos_phy_rd_sflx_downall(:,:,1,2), &
589  var_name(10), 'XY' ) ! [IN]
590  call fileio_write_var( restart_fid, var_id(11), atmos_phy_rd_sflx_downall(:,:,2,1), &
591  var_name(11), 'XY' ) ! [IN]
592  call fileio_write_var( restart_fid, var_id(12), atmos_phy_rd_sflx_downall(:,:,2,2), &
593  var_name(12), 'XY' ) ! [IN]
594 
595  endif
596 
597  return
599 
600 end module mod_atmos_phy_rd_vars
subroutine, public atmos_phy_rd_vars_restart_close
Close restart file.
subroutine, public atmos_phy_rd_vars_restart_create
Create restart file.
subroutine, public prc_mpistop
Abort MPI.
character(len=h_long), public atmos_phy_rd_restart_in_basename
basename of the restart file
subroutine, public atmos_phy_rd_vars_external_in(init_value_in)
Input from External I/O.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
character(len=h_mid), public atmos_phy_rd_restart_out_title
title of the output file
module STDIO
Definition: scale_stdio.F90:12
real(rp), dimension(:,:,:), allocatable, public atmos_phy_rd_rhot_t
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_up
module FILE I/O (netcdf)
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_sw_up
real(rp), public const_undef
Definition: scale_const.F90:43
module Statistics
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_lw_dn
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_cossza
module Atmosphere / Physics Radiation
character(len=h_long), public atmos_phy_rd_restart_out_basename
basename of the output file
module grid index
module TRACER
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_up
subroutine, public fileio_def_var(fid, vid, varname, desc, unit, axistype, datatype, timeintv)
Define a variable to file.
integer, public ia
of x whole cells (local, with HALO)
subroutine, public atmos_phy_rd_vars_restart_def_var
Define variables in restart file.
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
integer, public ka
of z whole cells (local, with HALO)
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_sflx_sw_dn
subroutine, public fileio_create(fid, basename, title, datatype, date, subsec, append, nozcoord)
Create/open a netCDF file.
module COMMUNICATION
Definition: scale_comm.F90:23
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_dn
module PROCESS
logical, public atmos_phy_rd_restart_output
output restart file?
subroutine, public atmos_phy_rd_vars_setup
Setup.
character(len=h_mid), public atmos_phy_rd_restart_out_dtype
REAL4 or REAL8.
module CONSTANT
Definition: scale_const.F90:14
subroutine, public atmos_phy_rd_vars_restart_write
Write restart.
subroutine, public fileio_enddef(fid)
Exit netCDF file define mode.
subroutine, public atmos_phy_rd_vars_restart_write_var
Write variables to restart file.
real(rp), dimension(:,:,:,:), allocatable, public atmos_phy_rd_sflx_downall
module profiler
Definition: scale_prof.F90:10
subroutine, public atmos_phy_rd_vars_restart_enddef
Exit netCDF define mode.
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_sw_dn
module PRECISION
subroutine, public atmos_phy_rd_vars_restart_read
Read restart.
subroutine, public atmos_phy_rd_vars_fillhalo
HALO Communication.
subroutine, public fileio_close(fid)
Close a netCDF file.
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_solins
real(rp), dimension(:,:), allocatable, public atmos_phy_rd_toaflx_lw_up
integer, public ja
of y whole cells (local, with HALO)