SCALE-RM
mod_ocean_vars.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_stdio
18  use scale_prof
19  use scale_debug
21 
22  use scale_const, only: &
23  i_sw => const_i_sw, &
24  i_lw => const_i_lw
25  !-----------------------------------------------------------------------------
26  implicit none
27  private
28  !-----------------------------------------------------------------------------
29  !
30  !++ Public procedure
31  !
32  public :: ocean_vars_setup
33  public :: ocean_vars_restart_read
34  public :: ocean_vars_restart_write
35  public :: ocean_vars_history
36  public :: ocean_vars_total
37  public :: ocean_vars_external_in
38 
43  public :: ocean_vars_restart_close
44 
45  !-----------------------------------------------------------------------------
46  !
47  !++ Public parameters & variables
48  !
49  logical, public :: ocean_restart_output = .false.
50 
51  character(len=H_LONG), public :: ocean_restart_in_basename = ''
52  character(len=H_LONG), public :: ocean_restart_out_basename = ''
53  character(len=H_MID), public :: ocean_restart_out_title = 'OCEAN restart'
54  character(len=H_MID), public :: ocean_restart_out_dtype = 'DEFAULT'
55 
56  ! prognostic variables
57  real(RP), public, allocatable :: ocean_temp (:,:)
58  real(RP), public, allocatable :: ocean_sfc_temp (:,:)
59  real(RP), public, allocatable :: ocean_sfc_albedo(:,:,:)
60  real(RP), public, allocatable :: ocean_sfc_z0m (:,:)
61  real(RP), public, allocatable :: ocean_sfc_z0h (:,:)
62  real(RP), public, allocatable :: ocean_sfc_z0e (:,:)
63 
64  ! tendency variables
65  real(RP), public, allocatable :: ocean_temp_t (:,:)
66  real(RP), public, allocatable :: ocean_sfc_temp_t (:,:)
67  real(RP), public, allocatable :: ocean_sfc_albedo_t(:,:,:)
68  real(RP), public, allocatable :: ocean_sfc_z0m_t (:,:)
69  real(RP), public, allocatable :: ocean_sfc_z0h_t (:,:)
70  real(RP), public, allocatable :: ocean_sfc_z0e_t (:,:)
71 
72  ! surface variables for restart
73  real(RP), public, allocatable :: ocean_sflx_mw (:,:)
74  real(RP), public, allocatable :: ocean_sflx_mu (:,:)
75  real(RP), public, allocatable :: ocean_sflx_mv (:,:)
76  real(RP), public, allocatable :: ocean_sflx_sh (:,:)
77  real(RP), public, allocatable :: ocean_sflx_lh (:,:)
78  real(RP), public, allocatable :: ocean_sflx_wh (:,:)
79  real(RP), public, allocatable :: ocean_sflx_evap(:,:)
80 
81  ! diagnostic variables
82  real(RP), public, allocatable :: ocean_u10(:,:)
83  real(RP), public, allocatable :: ocean_v10(:,:)
84  real(RP), public, allocatable :: ocean_t2 (:,:)
85  real(RP), public, allocatable :: ocean_q2 (:,:)
86 
87  ! recieved atmospheric variables
88  real(RP), public, allocatable :: atmos_temp (:,:)
89  real(RP), public, allocatable :: atmos_pres (:,:)
90  real(RP), public, allocatable :: atmos_w (:,:)
91  real(RP), public, allocatable :: atmos_u (:,:)
92  real(RP), public, allocatable :: atmos_v (:,:)
93  real(RP), public, allocatable :: atmos_dens (:,:)
94  real(RP), public, allocatable :: atmos_qv (:,:)
95  real(RP), public, allocatable :: atmos_pbl (:,:)
96  real(RP), public, allocatable :: atmos_sfc_pres (:,:)
97  real(RP), public, allocatable :: atmos_sflx_lw (:,:)
98  real(RP), public, allocatable :: atmos_sflx_sw (:,:)
99  real(RP), public, allocatable :: atmos_cossza (:,:)
100  real(RP), public, allocatable :: atmos_sflx_prec(:,:)
101 
102  !-----------------------------------------------------------------------------
103  !
104  !++ Private procedure
105  !
106  !-----------------------------------------------------------------------------
107  !
108  !++ Private parameters & variables
109  !
110  logical, private :: ocean_vars_checkrange = .false.
111 
112  integer, private, parameter :: vmax = 14
113  integer, private, parameter :: i_temp = 1
114  integer, private, parameter :: i_sfc_temp = 2
115  integer, private, parameter :: i_alb_lw = 3
116  integer, private, parameter :: i_alb_sw = 4
117  integer, private, parameter :: i_sfc_z0m = 5
118  integer, private, parameter :: i_sfc_z0h = 6
119  integer, private, parameter :: i_sfc_z0e = 7
120  integer, private, parameter :: i_sflx_mw = 8
121  integer, private, parameter :: i_sflx_mu = 9
122  integer, private, parameter :: i_sflx_mv = 10
123  integer, private, parameter :: i_sflx_sh = 11
124  integer, private, parameter :: i_sflx_lh = 12
125  integer, private, parameter :: i_sflx_wh = 13
126  integer, private, parameter :: i_sflx_evap = 14
127 
128  character(len=H_SHORT), private :: var_name(vmax)
129  character(len=H_MID), private :: var_desc(vmax)
130  character(len=H_SHORT), private :: var_unit(vmax)
131  integer, private :: var_id(vmax)
132  integer, private :: restart_fid = -1 ! file ID
133 
134  data var_name / 'OCEAN_TEMP', &
135  'OCEAN_SFC_TEMP', &
136  'OCEAN_ALB_LW', &
137  'OCEAN_ALB_SW', &
138  'OCEAN_SFC_Z0M', &
139  'OCEAN_SFC_Z0H', &
140  'OCEAN_SFC_Z0E', &
141  'OCEAN_SFLX_MW', &
142  'OCEAN_SFLX_MU', &
143  'OCEAN_SFLX_MV', &
144  'OCEAN_SFLX_SH', &
145  'OCEAN_SFLX_LH', &
146  'OCEAN_SFLX_WH', &
147  'OCEAN_SFLX_evap' /
148  data var_desc / 'temperature at uppermost ocean layer', &
149  'ocean surface skin temperature', &
150  'ocean surface albedo (longwave)', &
151  'ocean surface albedo (shortwave)', &
152  'ocean surface roughness length (momentum)', &
153  'ocean surface roughness length (heat)', &
154  'ocean surface roughness length (vapor)', &
155  'ocean surface w-momentum flux', &
156  'ocean surface u-momentum flux', &
157  'ocean surface v-momentum flux', &
158  'ocean surface sensible heat flux', &
159  'ocean surface latent heat flux', &
160  'ocean surface water heat flux', &
161  'ocean surface water vapor flux' /
162  data var_unit / 'K', &
163  'K', &
164  '0-1', &
165  '0-1', &
166  'm', &
167  'm', &
168  'm', &
169  'kg/m2/s', &
170  'kg/m2/s', &
171  'kg/m2/s', &
172  'J/m2/s', &
173  'J/m2/s', &
174  'J/m2/s', &
175  'kg/m2/s' /
176 
177  !-----------------------------------------------------------------------------
178 contains
179  !-----------------------------------------------------------------------------
181  subroutine ocean_vars_setup
182  use scale_process, only: &
184  use scale_const, only: &
185  undef => const_undef
186  implicit none
187 
188  namelist / param_ocean_vars / &
193  ocean_vars_checkrange
194 
195  integer :: ierr
196  integer :: iv
197  !---------------------------------------------------------------------------
198 
199  if( io_l ) write(io_fid_log,*)
200  if( io_l ) write(io_fid_log,*) '++++++ Module[VARS] / Categ[OCEAN] / Origin[SCALE-RM]'
201 
202  allocate( ocean_temp(ia,ja) )
203  allocate( ocean_sfc_temp(ia,ja) )
204  allocate( ocean_sfc_albedo(ia,ja,2) )
205  allocate( ocean_sfc_z0m(ia,ja) )
206  allocate( ocean_sfc_z0h(ia,ja) )
207  allocate( ocean_sfc_z0e(ia,ja) )
208  ocean_temp(:,:) = undef
209  ocean_sfc_temp(:,:) = undef
210  ocean_sfc_albedo(:,:,:) = undef
211  ocean_sfc_z0m(:,:) = undef
212  ocean_sfc_z0h(:,:) = undef
213  ocean_sfc_z0e(:,:) = undef
214 
215  allocate( ocean_temp_t(ia,ja) )
216  allocate( ocean_sfc_temp_t(ia,ja) )
217  allocate( ocean_sfc_albedo_t(ia,ja,2) )
218  allocate( ocean_sfc_z0m_t(ia,ja) )
219  allocate( ocean_sfc_z0h_t(ia,ja) )
220  allocate( ocean_sfc_z0e_t(ia,ja) )
221  ocean_temp_t(:,:) = undef
222  ocean_sfc_temp_t(:,:) = undef
223  ocean_sfc_albedo_t(:,:,:) = undef
224  ocean_sfc_z0m_t(:,:) = undef
225  ocean_sfc_z0h_t(:,:) = undef
226  ocean_sfc_z0e_t(:,:) = undef
227 
228  allocate( ocean_sflx_mw(ia,ja) )
229  allocate( ocean_sflx_mu(ia,ja) )
230  allocate( ocean_sflx_mv(ia,ja) )
231  allocate( ocean_sflx_sh(ia,ja) )
232  allocate( ocean_sflx_lh(ia,ja) )
233  allocate( ocean_sflx_wh(ia,ja) )
234  allocate( ocean_sflx_evap(ia,ja) )
235  ocean_sflx_mw(:,:) = undef
236  ocean_sflx_mu(:,:) = undef
237  ocean_sflx_mv(:,:) = undef
238  ocean_sflx_sh(:,:) = undef
239  ocean_sflx_lh(:,:) = undef
240  ocean_sflx_wh(:,:) = undef
241  ocean_sflx_evap(:,:) = undef
242 
243  allocate( ocean_u10(ia,ja) )
244  allocate( ocean_v10(ia,ja) )
245  allocate( ocean_t2(ia,ja) )
246  allocate( ocean_q2(ia,ja) )
247  ocean_u10(:,:) = undef
248  ocean_v10(:,:) = undef
249  ocean_t2(:,:) = undef
250  ocean_q2(:,:) = undef
251 
252  allocate( atmos_temp(ia,ja) )
253  allocate( atmos_pres(ia,ja) )
254  allocate( atmos_w(ia,ja) )
255  allocate( atmos_u(ia,ja) )
256  allocate( atmos_v(ia,ja) )
257  allocate( atmos_dens(ia,ja) )
258  allocate( atmos_qv(ia,ja) )
259  allocate( atmos_pbl(ia,ja) )
260  allocate( atmos_sfc_pres(ia,ja) )
261  allocate( atmos_sflx_lw(ia,ja) )
262  allocate( atmos_sflx_sw(ia,ja) )
263  allocate( atmos_cossza(ia,ja) )
264  allocate( atmos_sflx_prec(ia,ja) )
265  atmos_temp(:,:) = undef
266  atmos_pres(:,:) = undef
267  atmos_w(:,:) = undef
268  atmos_u(:,:) = undef
269  atmos_v(:,:) = undef
270  atmos_dens(:,:) = undef
271  atmos_qv(:,:) = undef
272  atmos_pbl(:,:) = undef
273  atmos_sfc_pres(:,:) = undef
274  atmos_sflx_lw(:,:) = undef
275  atmos_sflx_sw(:,:) = undef
276  atmos_cossza(:,:) = undef
277  atmos_sflx_prec(:,:) = undef
278 
279  !--- read namelist
280  rewind(io_fid_conf)
281  read(io_fid_conf,nml=param_ocean_vars,iostat=ierr)
282  if( ierr < 0 ) then !--- missing
283  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
284  elseif( ierr > 0 ) then !--- fatal error
285  write(*,*) 'xxx Not appropriate names in namelist PARAM_OCEAN_VARS. Check!'
286  call prc_mpistop
287  endif
288  if( io_lnml ) write(io_fid_log,nml=param_ocean_vars)
289 
290  if( io_l ) write(io_fid_log,*)
291  if( io_l ) write(io_fid_log,*) '*** List of prognostic variables (OCEAN) ***'
292  if( io_l ) write(io_fid_log,'(1x,A,A15,A,A32,3(A))') &
293  '*** |','VARNAME ','|', 'DESCRIPTION ','[', 'UNIT ',']'
294  do iv = 1, vmax
295  if( io_l ) write(io_fid_log,'(1x,A,i3,A,A15,A,A32,3(A))') &
296  '*** NO.',iv,'|',var_name(iv),'|',var_desc(iv),'[',var_unit(iv),']'
297 
298  enddo
299 
300  if( io_l ) write(io_fid_log,*)
301  if ( ocean_restart_in_basename /= '' ) then
302  if( io_l ) write(io_fid_log,*) '*** Restart input? : ', trim(ocean_restart_in_basename)
303  else
304  if( io_l ) write(io_fid_log,*) '*** Restart input? : NO'
305  endif
306  if ( ocean_restart_output &
307  .AND. ocean_restart_out_basename /= '' ) then
308  if( io_l ) write(io_fid_log,*) '*** Restart output? : ', trim(ocean_restart_out_basename)
309  else
310  if( io_l ) write(io_fid_log,*) '*** Restart output? : NO'
311  ocean_restart_output = .false.
312  endif
313 
314  return
315  end subroutine ocean_vars_setup
316 
317  !-----------------------------------------------------------------------------
319  subroutine ocean_vars_restart_read
320  use scale_fileio, only: &
321  fileio_read
322  use mod_ocean_admin, only: &
323  ocean_sw
324  implicit none
325  !---------------------------------------------------------------------------
326 
327  if( io_l ) write(io_fid_log,*)
328  if( io_l ) write(io_fid_log,*) '*** Input restart file (OCEAN) ***'
329 
330  if ( ocean_sw .and. ocean_restart_in_basename /= '' ) then
331  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(ocean_restart_in_basename)
332 
333  call fileio_read( ocean_temp(:,:), & ! [OUT]
334  ocean_restart_in_basename, var_name(i_temp), 'XY', step=1 ) ! [IN]
335  call fileio_read( ocean_sfc_temp(:,:), & ! [OUT]
336  ocean_restart_in_basename, var_name(i_sfc_temp), 'XY', step=1 ) ! [IN]
337  call fileio_read( ocean_sfc_albedo(:,:,i_lw), & ! [OUT]
338  ocean_restart_in_basename, var_name(i_alb_lw), 'XY', step=1 ) ! [IN]
339  call fileio_read( ocean_sfc_albedo(:,:,i_sw), & ! [OUT]
340  ocean_restart_in_basename, var_name(i_alb_sw), 'XY', step=1 ) ! [IN]
341  call fileio_read( ocean_sfc_z0m(:,:), & ! [OUT]
342  ocean_restart_in_basename, var_name(i_sfc_z0m), 'XY', step=1 ) ! [IN]
343  call fileio_read( ocean_sfc_z0h(:,:), & ! [OUT]
344  ocean_restart_in_basename, var_name(i_sfc_z0h), 'XY', step=1 ) ! [IN]
345  call fileio_read( ocean_sfc_z0e(:,:), & ! [OUT]
346  ocean_restart_in_basename, var_name(i_sfc_z0e), 'XY', step=1 ) ! [IN]
347 
348  call fileio_read( ocean_sflx_mw(:,:), & ! [OUT]
349  ocean_restart_in_basename, var_name(i_sflx_mw), 'XY', step=1 ) ! [IN]
350  call fileio_read( ocean_sflx_mu(:,:), & ! [OUT]
351  ocean_restart_in_basename, var_name(i_sflx_mu), 'XY', step=1 ) ! [IN]
352  call fileio_read( ocean_sflx_mv(:,:), & ! [OUT]
353  ocean_restart_in_basename, var_name(i_sflx_mv), 'XY', step=1 ) ! [IN]
354  call fileio_read( ocean_sflx_sh(:,:), & ! [OUT]
355  ocean_restart_in_basename, var_name(i_sflx_sh), 'XY', step=1 ) ! [IN]
356  call fileio_read( ocean_sflx_lh(:,:), & ! [OUT]
357  ocean_restart_in_basename, var_name(i_sflx_lh), 'XY', step=1 ) ! [IN]
358  call fileio_read( ocean_sflx_wh(:,:), & ! [OUT]
359  ocean_restart_in_basename, var_name(i_sflx_wh), 'XY', step=1 ) ! [IN]
360  call fileio_read( ocean_sflx_evap(:,:), & ! [OUT]
361  ocean_restart_in_basename, var_name(i_sflx_evap), 'XY', step=1 ) ! [IN]
362 
363  call ocean_vars_total
364  else
365  if( io_l ) write(io_fid_log,*) '*** restart file for ocean is not specified.'
366  endif
367 
368  return
369  end subroutine ocean_vars_restart_read
370 
371  !-----------------------------------------------------------------------------
373  subroutine ocean_vars_restart_write
374  use scale_time, only: &
376  use scale_fileio, only: &
377  fileio_write
378  use mod_ocean_admin, only: &
379  ocean_sw
380  implicit none
381 
382  character(len=20) :: timelabel
383  character(len=H_LONG) :: basename
384  !---------------------------------------------------------------------------
385 
386  if ( ocean_sw .and. ocean_restart_out_basename /= '' ) then
387 
388  call time_gettimelabel( timelabel )
389  write(basename,'(A,A,A)') trim(ocean_restart_out_basename), '_', trim(timelabel)
390 
391  if( io_l ) write(io_fid_log,*)
392  if( io_l ) write(io_fid_log,*) '*** Output restart file (OCEAN) ***'
393  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
394 
395  call ocean_vars_total
396 
397  call fileio_write( ocean_temp(:,:), basename, ocean_restart_out_title, & ! [IN]
398  var_name(i_temp), var_desc(i_temp), var_unit(i_temp), & ! [IN]
399  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
400  call fileio_write( ocean_sfc_temp(:,:), basename, ocean_restart_out_title, & ! [IN]
401  var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp), & ! [IN]
402  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
403  call fileio_write( ocean_sfc_albedo(:,:,i_lw), basename, ocean_restart_out_title, & ! [IN]
404  var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw), & ! [IN]
405  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
406  call fileio_write( ocean_sfc_albedo(:,:,i_sw), basename, ocean_restart_out_title, & ! [IN]
407  var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw), & ! [IN]
408  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
409  call fileio_write( ocean_sfc_z0m(:,:), basename, ocean_restart_out_title, & ! [IN]
410  var_name(i_sfc_z0m), var_desc(i_sfc_z0m), var_unit(i_sfc_z0m), & ! [IN]
411  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
412  call fileio_write( ocean_sfc_z0h(:,:), basename, ocean_restart_out_title, & ! [IN]
413  var_name(i_sfc_z0h), var_desc(i_sfc_z0h), var_unit(i_sfc_z0h), & ! [IN]
414  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
415  call fileio_write( ocean_sfc_z0e(:,:), basename, ocean_restart_out_title, & ! [IN]
416  var_name(i_sfc_z0e), var_desc(i_sfc_z0e), var_unit(i_sfc_z0e), & ! [IN]
417  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
418  call fileio_write( ocean_sflx_mw(:,:), basename, ocean_restart_out_title, & ! [IN]
419  var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw), & ! [IN]
420  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
421  call fileio_write( ocean_sflx_mu(:,:), basename, ocean_restart_out_title, & ! [IN]
422  var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu), & ! [IN]
423  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
424  call fileio_write( ocean_sflx_mv(:,:), basename, ocean_restart_out_title, & ! [IN]
425  var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv), & ! [IN]
426  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
427  call fileio_write( ocean_sflx_sh(:,:), basename, ocean_restart_out_title, & ! [IN]
428  var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh), & ! [IN]
429  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
430  call fileio_write( ocean_sflx_lh(:,:), basename, ocean_restart_out_title, & ! [IN]
431  var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh), & ! [IN]
432  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
433  call fileio_write( ocean_sflx_wh(:,:), basename, ocean_restart_out_title, & ! [IN]
434  var_name(i_sflx_wh), var_desc(i_sflx_wh), var_unit(i_sflx_wh), & ! [IN]
435  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
436  call fileio_write( ocean_sflx_evap(:,:), basename, ocean_restart_out_title, & ! [IN]
437  var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap), & ! [IN]
438  'XY', ocean_restart_out_dtype, nohalo=.true. ) ! [IN]
439 
440  endif
441 
442  return
443  end subroutine ocean_vars_restart_write
444 
445  !-----------------------------------------------------------------------------
447  subroutine ocean_vars_history
448  use scale_history, only: &
449  hist_in
450  implicit none
451  !---------------------------------------------------------------------------
452 
453  if ( ocean_vars_checkrange ) then
454  call valcheck( ocean_temp(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_temp), &
455  __file__, __line__ )
456  call valcheck( ocean_sfc_temp(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_sfc_temp), &
457  __file__, __line__ )
458  call valcheck( ocean_sfc_albedo(is:ie,js:je,i_lw), 0.0_rp, 2.0_rp, var_name(i_alb_lw), &
459  __file__, __line__ )
460  call valcheck( ocean_sfc_albedo(is:ie,js:je,i_sw), 0.0_rp, 2.0_rp, var_name(i_alb_sw), &
461  __file__, __line__ )
462  call valcheck( ocean_sfc_z0m(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_sfc_z0m), &
463  __file__, __line__ )
464  call valcheck( ocean_sfc_z0h(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_sfc_z0h), &
465  __file__, __line__ )
466  call valcheck( ocean_sfc_z0e(is:ie,js:je), 0.0_rp, 1000.0_rp, var_name(i_sfc_z0e), &
467  __file__, __line__ )
468  endif
469 
470  call hist_in( ocean_temp(:,:), var_name(i_temp), var_desc(i_temp), var_unit(i_temp) )
471  call hist_in( ocean_sfc_temp(:,:), var_name(i_sfc_temp), var_desc(i_sfc_temp), var_unit(i_sfc_temp) )
472  call hist_in( ocean_sfc_albedo(:,:,i_lw), var_name(i_alb_lw), var_desc(i_alb_lw), var_unit(i_alb_lw) )
473  call hist_in( ocean_sfc_albedo(:,:,i_sw), var_name(i_alb_sw), var_desc(i_alb_sw), var_unit(i_alb_sw) )
474  call hist_in( ocean_sfc_z0m(:,:), var_name(i_sfc_z0m), var_desc(i_sfc_z0m), var_unit(i_sfc_z0m) )
475  call hist_in( ocean_sfc_z0h(:,:), var_name(i_sfc_z0h), var_desc(i_sfc_z0h), var_unit(i_sfc_z0h) )
476  call hist_in( ocean_sfc_z0e(:,:), var_name(i_sfc_z0e), var_desc(i_sfc_z0e), var_unit(i_sfc_z0e) )
477 
478  call hist_in( ocean_sflx_mw(:,:), var_name(i_sflx_mw), var_desc(i_sflx_mw), var_unit(i_sflx_mw) )
479  call hist_in( ocean_sflx_mu(:,:), var_name(i_sflx_mu), var_desc(i_sflx_mu), var_unit(i_sflx_mu) )
480  call hist_in( ocean_sflx_mv(:,:), var_name(i_sflx_mv), var_desc(i_sflx_mv), var_unit(i_sflx_mv) )
481  call hist_in( ocean_sflx_sh(:,:), var_name(i_sflx_sh), var_desc(i_sflx_sh), var_unit(i_sflx_sh) )
482  call hist_in( ocean_sflx_lh(:,:), var_name(i_sflx_lh), var_desc(i_sflx_lh), var_unit(i_sflx_lh) )
483  call hist_in( ocean_sflx_wh(:,:), var_name(i_sflx_wh), var_desc(i_sflx_wh), var_unit(i_sflx_wh) )
484  call hist_in( ocean_sflx_evap(:,:), var_name(i_sflx_evap), var_desc(i_sflx_evap), var_unit(i_sflx_evap) )
485 
486  return
487  end subroutine ocean_vars_history
488 
489  !-----------------------------------------------------------------------------
491  subroutine ocean_vars_total
492  use scale_rm_statistics, only: &
494  stat_total
495  implicit none
496 
497  real(RP) :: total
498  !---------------------------------------------------------------------------
499 
500  if ( statistics_checktotal ) then
501 
502  call stat_total( total, ocean_temp(:,:), var_name(i_temp) )
503  call stat_total( total, ocean_sfc_temp(:,:), var_name(i_sfc_temp) )
504  call stat_total( total, ocean_sfc_albedo(:,:,i_lw), var_name(i_alb_lw) )
505  call stat_total( total, ocean_sfc_albedo(:,:,i_sw), var_name(i_alb_sw) )
506  call stat_total( total, ocean_sfc_z0m(:,:), var_name(i_sfc_z0m) )
507  call stat_total( total, ocean_sfc_z0h(:,:), var_name(i_sfc_z0h) )
508  call stat_total( total, ocean_sfc_z0e(:,:), var_name(i_sfc_z0e) )
509 
510  call stat_total( total, ocean_sflx_mw(:,:), var_name(i_sflx_mw) )
511  call stat_total( total, ocean_sflx_mu(:,:), var_name(i_sflx_mu) )
512  call stat_total( total, ocean_sflx_mv(:,:), var_name(i_sflx_mv) )
513  call stat_total( total, ocean_sflx_sh(:,:), var_name(i_sflx_sh) )
514  call stat_total( total, ocean_sflx_lh(:,:), var_name(i_sflx_lh) )
515  call stat_total( total, ocean_sflx_wh(:,:), var_name(i_sflx_wh) )
516  call stat_total( total, ocean_sflx_evap(:,:), var_name(i_sflx_evap) )
517 
518  endif
519 
520  return
521  end subroutine ocean_vars_total
522 
523  !-----------------------------------------------------------------------------
525  subroutine ocean_vars_external_in( &
526  OCEAN_TEMP_in, &
527  OCEAN_SFC_TEMP_in, &
528  OCEAN_SFC_albedo_in, &
529  OCEAN_SFC_Z0M_in, &
530  OCEAN_SFC_Z0H_in, &
531  OCEAN_SFC_Z0E_in )
532  implicit none
533 
534  real(RP), intent(in) :: OCEAN_TEMP_in (ia,ja)
535  real(RP), intent(in) :: OCEAN_SFC_TEMP_in (ia,ja)
536  real(RP), intent(in) :: OCEAN_SFC_albedo_in(ia,ja,2)
537  real(RP), intent(in) :: OCEAN_SFC_Z0M_in (ia,ja)
538  real(RP), intent(in) :: OCEAN_SFC_Z0H_in (ia,ja)
539  real(RP), intent(in) :: OCEAN_SFC_Z0E_in (ia,ja)
540  !---------------------------------------------------------------------------
541 
542  if( io_l ) write(io_fid_log,*)
543  if( io_l ) write(io_fid_log,*) '*** External Input file (ocean) ***'
544 
545  ocean_temp(:,:) = ocean_temp_in(:,:)
546  ocean_sfc_temp(:,:) = ocean_sfc_temp_in(:,:)
547  ocean_sfc_albedo(:,:,:) = ocean_sfc_albedo_in(:,:,:)
548  ocean_sfc_z0m(:,:) = ocean_sfc_z0m_in(:,:)
549  ocean_sfc_z0h(:,:) = ocean_sfc_z0h_in(:,:)
550  ocean_sfc_z0e(:,:) = ocean_sfc_z0e_in(:,:)
551 
552  ocean_sflx_mw(:,:) = 0.0_rp
553  ocean_sflx_mu(:,:) = 0.0_rp
554  ocean_sflx_mv(:,:) = 0.0_rp
555  ocean_sflx_sh(:,:) = 0.0_rp
556  ocean_sflx_lh(:,:) = 0.0_rp
557  ocean_sflx_wh(:,:) = 0.0_rp
558  ocean_sflx_evap(:,:) = 0.0_rp
559 
560  call ocean_vars_total
561 
562  return
563  end subroutine ocean_vars_external_in
564 
565  !-----------------------------------------------------------------------------
567  subroutine ocean_vars_restart_create
568  use scale_time, only: &
570  use scale_fileio, only: &
572  use mod_ocean_admin, only: &
573  ocean_sw
574  implicit none
575 
576  character(len=20) :: timelabel
577  character(len=H_LONG) :: basename
578  !---------------------------------------------------------------------------
579 
580  if ( ocean_sw .and. ocean_restart_out_basename /= '' ) then
581 
582  call time_gettimelabel( timelabel )
583  write(basename,'(A,A,A)') trim(ocean_restart_out_basename), '_', trim(timelabel)
584 
585  if( io_l ) write(io_fid_log,*)
586  if( io_l ) write(io_fid_log,*) '*** Output restart file (OCEAN) ***'
587  if( io_l ) write(io_fid_log,*) '*** basename: ', trim(basename)
588 
590  endif
591 
592  return
593  end subroutine ocean_vars_restart_create
594 
595  !-----------------------------------------------------------------------------
597  subroutine ocean_vars_restart_enddef
598  use scale_fileio, only: &
600  implicit none
601 
602  if ( restart_fid .NE. -1 ) then
603  call fileio_enddef( restart_fid ) ! [IN]
604  endif
605 
606  return
607  end subroutine ocean_vars_restart_enddef
608 
609  !-----------------------------------------------------------------------------
611  subroutine ocean_vars_restart_close
612  use scale_fileio, only: &
614  implicit none
615 
616  if ( restart_fid .NE. -1 ) then
617  call fileio_close( restart_fid ) ! [IN]
618  restart_fid = -1
619  endif
620 
621  return
622  end subroutine ocean_vars_restart_close
623 
624  !-----------------------------------------------------------------------------
626  subroutine ocean_vars_restart_def_var
627  use scale_fileio, only: &
629  implicit none
630 
631  !---------------------------------------------------------------------------
632 
633  if ( restart_fid .NE. -1 ) then
634 
635  call fileio_def_var( restart_fid, var_id(i_temp), var_name(i_temp), var_desc(i_temp), &
636  var_unit(i_temp), 'XY', ocean_restart_out_dtype)
637  call fileio_def_var( restart_fid, var_id(i_sfc_temp), var_name(i_sfc_temp), var_desc(i_sfc_temp), &
638  var_unit(i_sfc_temp), 'XY', ocean_restart_out_dtype)
639  call fileio_def_var( restart_fid, var_id(i_alb_lw), var_name(i_alb_lw), var_desc(i_alb_lw), &
640  var_unit(i_alb_lw), 'XY', ocean_restart_out_dtype)
641  call fileio_def_var( restart_fid, var_id(i_alb_sw), var_name(i_alb_sw), var_desc(i_alb_sw), &
642  var_unit(i_alb_sw), 'XY', ocean_restart_out_dtype)
643  call fileio_def_var( restart_fid, var_id(i_sfc_z0m), var_name(i_sfc_z0m), var_desc(i_sfc_z0m), &
644  var_unit(i_sfc_z0m), 'XY', ocean_restart_out_dtype)
645  call fileio_def_var( restart_fid, var_id(i_sfc_z0h), var_name(i_sfc_z0h), var_desc(i_sfc_z0h), &
646  var_unit(i_sfc_z0h), 'XY', ocean_restart_out_dtype)
647  call fileio_def_var( restart_fid, var_id(i_sfc_z0e), var_name(i_sfc_z0e), var_desc(i_sfc_z0e), &
648  var_unit(i_sfc_z0e), 'XY', ocean_restart_out_dtype)
649  call fileio_def_var( restart_fid, var_id(i_sflx_mw), var_name(i_sflx_mw), var_desc(i_sflx_mw), &
650  var_unit(i_sflx_mw), 'XY', ocean_restart_out_dtype)
651  call fileio_def_var( restart_fid, var_id(i_sflx_mu), var_name(i_sflx_mu), var_desc(i_sflx_mu), &
652  var_unit(i_sflx_mu), 'XY', ocean_restart_out_dtype)
653  call fileio_def_var( restart_fid, var_id(i_sflx_mv), var_name(i_sflx_mv), var_desc(i_sflx_mv), &
654  var_unit(i_sflx_mv), 'XY', ocean_restart_out_dtype)
655  call fileio_def_var( restart_fid, var_id(i_sflx_sh), var_name(i_sflx_sh), var_desc(i_sflx_sh), &
656  var_unit(i_sflx_sh), 'XY', ocean_restart_out_dtype)
657  call fileio_def_var( restart_fid, var_id(i_sflx_lh), var_name(i_sflx_lh), var_desc(i_sflx_lh), &
658  var_unit(i_sflx_lh), 'XY', ocean_restart_out_dtype)
659  call fileio_def_var( restart_fid, var_id(i_sflx_wh), var_name(i_sflx_wh), var_desc(i_sflx_wh), &
660  var_unit(i_sflx_wh), 'XY', ocean_restart_out_dtype)
661  call fileio_def_var( restart_fid, var_id(i_sflx_evap), var_name(i_sflx_evap), var_desc(i_sflx_evap), &
662  var_unit(i_sflx_evap), 'XY', ocean_restart_out_dtype)
663 
664  endif
665 
666  return
667  end subroutine ocean_vars_restart_def_var
668 
669  !-----------------------------------------------------------------------------
672  use scale_fileio, only: &
673  fileio_write_var
674  implicit none
675 
676  !---------------------------------------------------------------------------
677 
678  if ( restart_fid .NE. -1 ) then
679 
680  call ocean_vars_total
681 
682  call fileio_write_var( restart_fid, var_id(i_temp), ocean_temp(:,:), & ! [IN]
683  var_name(i_temp), 'XY', nohalo=.true. ) ! [IN]
684  call fileio_write_var( restart_fid, var_id(i_sfc_temp), ocean_sfc_temp(:,:), & ! [IN]
685  var_name(i_sfc_temp), 'XY', nohalo=.true. ) ! [IN]
686  call fileio_write_var( restart_fid, var_id(i_alb_lw), ocean_sfc_albedo(:,:,i_lw), & ! [IN]
687  var_name(i_alb_lw), 'XY', nohalo=.true. ) ! [IN]
688  call fileio_write_var( restart_fid, var_id(i_alb_sw), ocean_sfc_albedo(:,:,i_sw), & ! [IN]
689  var_name(i_alb_sw), 'XY', nohalo=.true. ) ! [IN]
690  call fileio_write_var( restart_fid, var_id(i_sfc_z0m), ocean_sfc_z0m(:,:), & ! [IN]
691  var_name(i_sfc_z0m), 'XY', nohalo=.true. ) ! [IN]
692  call fileio_write_var( restart_fid, var_id(i_sfc_z0h), ocean_sfc_z0h(:,:), & ! [IN]
693  var_name(i_sfc_z0h), 'XY', nohalo=.true. ) ! [IN]
694  call fileio_write_var( restart_fid, var_id(i_sfc_z0e), ocean_sfc_z0e(:,:), & ! [IN]
695  var_name(i_sfc_z0e), 'XY', nohalo=.true. ) ! [IN]
696  call fileio_write_var( restart_fid, var_id(i_sflx_mw), ocean_sflx_mw(:,:), & ! [IN]
697  var_name(i_sflx_mw), 'XY', nohalo=.true. ) ! [IN]
698  call fileio_write_var( restart_fid, var_id(i_sflx_mu), ocean_sflx_mu(:,:), & ! [IN]
699  var_name(i_sflx_mu), 'XY', nohalo=.true. ) ! [IN]
700  call fileio_write_var( restart_fid, var_id(i_sflx_mv), ocean_sflx_mv(:,:), & ! [IN]
701  var_name(i_sflx_mv), 'XY', nohalo=.true. ) ! [IN]
702  call fileio_write_var( restart_fid, var_id(i_sflx_sh), ocean_sflx_sh(:,:), & ! [IN]
703  var_name(i_sflx_sh), 'XY', nohalo=.true. ) ! [IN]
704  call fileio_write_var( restart_fid, var_id(i_sflx_lh), ocean_sflx_lh(:,:), & ! [IN]
705  var_name(i_sflx_lh), 'XY', nohalo=.true. ) ! [IN]
706  call fileio_write_var( restart_fid, var_id(i_sflx_wh), ocean_sflx_wh(:,:), & ! [IN]
707  var_name(i_sflx_wh), 'XY', nohalo=.true. ) ! [IN]
708  call fileio_write_var( restart_fid, var_id(i_sflx_evap), ocean_sflx_evap(:,:), & ! [IN]
709  var_name(i_sflx_evap), 'XY', nohalo=.true. ) ! [IN]
710 
711  endif
712 
713  return
714  end subroutine ocean_vars_restart_write_var
715 
716 end module mod_ocean_vars
character(len=h_mid), public ocean_restart_out_dtype
REAL4 or REAL8.
real(rp), dimension(:,:), allocatable, public ocean_v10
ocean surface velocity v at 10m [m/s]
integer, public is
start point of inner domain: x, local
module DEBUG
Definition: scale_debug.F90:13
logical, public ocean_sw
real(rp), dimension(:,:), allocatable, public atmos_w
logical, public statistics_checktotal
calc&report variable totals to logfile?
real(rp), dimension(:,:), allocatable, public ocean_sfc_temp_t
tendency of OCEAN_SFC_TEMP
integer, public je
end point of inner domain: y, local
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0e_t
tendency of OCEAN_SFC_Z0E
real(rp), dimension(:,:,:), allocatable, public ocean_sfc_albedo
ocean surface albedo [0-1]
real(rp), dimension(:,:), allocatable, public atmos_dens
integer, public const_i_lw
long-wave radiation index
Definition: scale_const.F90:98
subroutine, public prc_mpistop
Abort MPI.
real(rp), dimension(:,:,:), allocatable, public ocean_sfc_albedo_t
tendency of OCEAN_SFC_alebdo
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0e
ocean surface roughness length for vapor [m]
real(rp), dimension(:,:), allocatable, public ocean_temp
temperature at uppermost ocean layer [K]
subroutine, public ocean_vars_restart_write
Write ocean restart.
real(rp), dimension(:,:), allocatable, public atmos_v
subroutine, public ocean_vars_history
History output set for ocean variables.
module STDIO
Definition: scale_stdio.F90:12
real(rp), dimension(:,:), allocatable, public ocean_sflx_wh
ocean surface water heat flux [J/m2/s]
subroutine, public ocean_vars_restart_def_var
Define ocean variables in restart file.
real(rp), dimension(:,:), allocatable, public atmos_sflx_lw
subroutine, public ocean_vars_restart_enddef
Exit netCDF define mode.
module FILE I/O (netcdf)
real(rp), dimension(:,:), allocatable, public ocean_temp_t
tendency of OCEAN_TEMP
real(rp), public const_undef
Definition: scale_const.F90:43
module Statistics
subroutine, public ocean_vars_restart_create
Create ocean restart file.
module grid index
real(rp), dimension(:,:), allocatable, public atmos_cossza
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)
real(rp), dimension(:,:), allocatable, public ocean_sflx_mv
ocean surface v-momentum flux [kg/m2/s]
subroutine, public time_gettimelabel(timelabel)
generate time label
Definition: scale_time.F90:90
subroutine, public ocean_vars_restart_write_var
Write ocean variables to restart file.
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_qv
subroutine, public ocean_vars_total
Budget monitor for ocean.
subroutine, public fileio_create(fid, basename, title, datatype, date, subsec, append, nozcoord)
Create/open a netCDF file.
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0h_t
tendency of OCEAN_SFC_Z0H
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
module PROCESS
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
module Ocean admin
subroutine, public ocean_vars_external_in(OCEAN_TEMP_in, OCEAN_SFC_TEMP_in, OCEAN_SFC_albedo_in, OCEAN_SFC_Z0M_in, OCEAN_SFC_Z0H_in, OCEAN_SFC_Z0E_in)
Input from External I/O.
real(rp), dimension(:,:), allocatable, public atmos_temp
subroutine, public ocean_vars_restart_read
Read ocean restart.
real(rp), dimension(:,:), allocatable, public ocean_sflx_mw
ocean surface w-momentum flux [kg/m2/s]
module CONSTANT
Definition: scale_const.F90:14
real(rp), dimension(:,:), allocatable, public ocean_sflx_mu
ocean surface u-momentum flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public ocean_q2
ocean surface water vapor at 2m [kg/kg]
subroutine, public fileio_enddef(fid)
Exit netCDF file define mode.
real(rp), dimension(:,:), allocatable, public atmos_u
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
real(rp), dimension(:,:), allocatable, public atmos_sflx_sw
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0m
ocean surface roughness length for momentum [m]
real(rp), dimension(:,:), allocatable, public atmos_pbl
logical, public io_lnml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:60
integer, public const_i_sw
short-wave radiation index
Definition: scale_const.F90:99
module PRECISION
subroutine, public ocean_vars_setup
Setup.
real(rp), dimension(:,:), allocatable, public ocean_sflx_sh
ocean surface sensible heat flux [J/m2/s]
character(len=h_long), public ocean_restart_in_basename
basename of the input file
module HISTORY
real(rp), dimension(:,:), allocatable, public ocean_sfc_temp
ocean surface skin temperature [K]
subroutine, public fileio_close(fid)
Close a netCDF file.
character(len=h_long), public ocean_restart_out_basename
basename of the output file
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0m_t
tendency of OCEAN_SFC_Z0M
logical, public ocean_restart_output
output restart file?
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
subroutine, public ocean_vars_restart_close
Close restart file.
real(rp), dimension(:,:), allocatable, public atmos_pres
real(rp), dimension(:,:), allocatable, public ocean_sflx_lh
ocean surface latent heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public ocean_u10
ocean surface velocity u at 10m [m/s]
real(rp), dimension(:,:), allocatable, public ocean_sflx_evap
ocean surface water vapor flux [kg/m2/s]
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0h
ocean surface roughness length for heat [m]
real(rp), dimension(:,:), allocatable, public ocean_t2
ocean surface temperature at 2m [K]
module OCEAN Variables
character(len=h_mid), public ocean_restart_out_title
title of the output file
integer, public ja
of y whole cells (local, with HALO)