SCALE-RM
mod_ocean_driver.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
10 #include "scalelib.h"
12  !-----------------------------------------------------------------------------
13  !
14  !++ used modules
15  !
16  use scale_precision
17  use scale_io
18  use scale_prof
20  use scale_tracer
22  !-----------------------------------------------------------------------------
23  implicit none
24  private
25  !-----------------------------------------------------------------------------
26  !
27  !++ Public procedure
28  !
29  public :: ocean_driver_setup
30  public :: ocean_driver_finalize
32  public :: ocean_driver_update
33  public :: ocean_surface_get
34  public :: ocean_surface_set
35 
36  !-----------------------------------------------------------------------------
37  !
38  !++ Public parameters & variables
39  !
40  !-----------------------------------------------------------------------------
41  !
42  !++ Private procedure
43  !
44  !-----------------------------------------------------------------------------
45  !
46  !++ Private parameters & variables
47  !
48  real(RP), private, allocatable :: WSTR (:,:)
49  real(RP), private, allocatable :: QVEF (:,:)
50  real(RP), private, allocatable :: SR (:,:)
51  real(RP), private, allocatable :: ATMOS_W(:,:)
52 
53  !-----------------------------------------------------------------------------
54 contains
55  !-----------------------------------------------------------------------------
57  subroutine ocean_driver_setup
58  use scale_prc, only: &
59  prc_abort
60  use scale_const, only: &
61  huge => const_huge
62  use mod_ocean_admin, only: &
63  ocean_do, &
69  use scale_cpl_phy_sfc_fixed_temp, only: &
71  use scale_atmos_hydrometeor, only: &
73  use scale_ocean_dyn_slab, only: &
75  use scale_ocean_dyn_offline, only: &
77  use scale_ocean_phy_ice_simple, only: &
79  use scale_ocean_phy_albedo, only: &
84  use scale_ocean_phy_roughness, only: &
91  use scale_ocean_phy_tc, only: &
93  use scale_ocean_grid_cartesc, only: &
95  implicit none
96  !---------------------------------------------------------------------------
97 
98  log_newline
99  log_info("OCEAN_driver_setup",*) 'Setup'
100 
101  if ( ocean_do ) then
102 
103  select case ( ocean_dyn_type )
104  case ( 'SLAB' )
105  call ocean_dyn_slab_setup( cdz(oks) )
106  case ( 'OFFLINE' )
108  case ( 'INIT' )
109  ! do nothing
110  case default
111  log_error("OCEAN_driver_setup",*) 'OCEAN_DYN_TYPE is invalid: ', trim(ocean_dyn_type)
112  call prc_abort
113  end select
114 
115  select case ( ocean_sfc_type )
116  case ( 'FIXED-TEMP' )
118  case default
119  log_error("OCEAN_driver_setup",*) 'OCEAN_SFC_TYPE is invalid: ', trim(ocean_sfc_type)
120  call prc_abort
121  end select
122 
123  select case ( ocean_ice_type )
124  case ( 'NONE' )
125  case ( 'SIMPLE' )
127  case ( 'INIT' )
128  case default
129  log_error("OCEAN_driver_setup",*) 'OCEAN_ICE_TYPE is invalid: ', trim(ocean_ice_type)
130  call prc_abort
131  end select
132 
133  ! surface albedo
134  select case ( ocean_alb_type )
135  case ( 'NAKAJIMA00' )
139  case ( 'CONST' )
141  case ( 'INIT' )
142  ! do nothing
143  case default
144  log_error("OCEAN_driver_setup",*) 'OCEAN_ALB_TYPE is invalid: ', trim(ocean_alb_type)
145  call prc_abort
146  end select
147 
148  ! surface roughness length
149  select case ( ocean_rgn_type )
150  case ( 'MILLER92' )
153  case ( 'MOON07' )
156  case ( 'CONST' )
158  case ( 'INIT' )
159  ! do nothing
160  case default
161  log_error("OCEAN_driver_setup",*) 'OCEAN_RGN_TYPE is invalid: ', trim(ocean_rgn_type)
162  call prc_abort
163  end select
164 
165  ! thermal conductivity
167 
168  allocate( wstr(oia,oja) )
169  allocate( qvef(oia,oja) )
170  allocate( sr(oia,oja) )
171  allocate( atmos_w(oia,oja) )
172  wstr(:,:) = huge
173  if ( atmos_hydrometeor_dry ) then
174  qvef(:,:) = 0.0_rp
175  else
176  qvef(:,:) = 1.0_rp
177  end if
178  sr(:,:) = 0.0_rp
179  atmos_w(:,:) = 0.0_rp ! slope of the sea surface is zero
180  !$acc enter data copyin(WSTR, QVEF, SR, ATMOS_W)
181 
182  endif
183 
184  return
185  end subroutine ocean_driver_setup
186 
187  !-----------------------------------------------------------------------------
189  subroutine ocean_driver_finalize
190  use mod_ocean_admin, only: &
191  ocean_do, &
192  ocean_dyn_type, &
193  ocean_ice_type, &
194  ocean_alb_type, &
196  implicit none
197  !---------------------------------------------------------------------------
198 
199  log_newline
200  log_info("OCEAN_driver_finalize",*) 'Finalize'
201 
202  if ( ocean_do ) then
203 
204  select case ( ocean_dyn_type )
205  case ( 'SLAB' )
206  case ( 'OFFLINE' )
207  case ( 'INIT' )
208  end select
209 
210  select case ( ocean_ice_type )
211  case ( 'NONE' )
212  case ( 'SIMPLE' )
213  case ( 'INIT' )
214  end select
215 
216  ! surface albedo
217  select case ( ocean_alb_type )
218  case ( 'NAKAJIMA00' )
219  case ( 'CONST' )
220  case ( 'INIT' )
221  end select
222 
223  ! surface roughness length
224  select case ( ocean_rgn_type )
225  case ( 'MILLER92' )
226  case ( 'MOON07' )
227  case ( 'CONST' )
228  case ( 'INIT' )
229  end select
230 
231  !$acc exit data delete(WSTR, QVEF, SR, ATMOS_W)
232  deallocate( wstr )
233  deallocate( qvef )
234  deallocate( sr )
235  deallocate( atmos_w )
236 
237  endif
238 
239  return
240  end subroutine ocean_driver_finalize
241 
242  !-----------------------------------------------------------------------------
244  subroutine ocean_driver_calc_tendency( force )
245  use scale_const, only: &
246  eps => const_eps
247  use scale_time, only: &
248  dt => time_dtsec_ocean
249  use scale_statistics, only: &
251  statistics_total
252  use scale_landuse, only: &
253  exists_ocean => landuse_exists_ocean
254  use scale_atmos_grid_cartesc_real, only: &
255  real_z1 => atmos_grid_cartesc_real_z1
256  use scale_atmos_hydrometeor, only: &
257  hydrometeor_lhv => atmos_hydrometeor_lhv, &
258  hydrometeor_lhs => atmos_hydrometeor_lhs, &
260  cv_water, &
261  cv_ice, &
262  lhf, &
263  i_qv
264  use scale_ocean_grid_cartesc_real, only: &
269  use scale_ocean_grid_cartesc_real, only: &
272  use scale_cpl_phy_sfc_fixed_temp, only: &
274  use scale_ocean_phy_albedo, only: &
279  use scale_ocean_phy_roughness, only: &
286  use scale_ocean_phy_tc, only: &
288  use scale_ocean_phy_ice_simple, only: &
290  use scale_bulkflux, only: &
291  bulkflux_diagnose_scales
292  use mod_atmos_admin, only: &
294  use mod_atmos_phy_ch_driver, only: &
296  use mod_ocean_admin, only: &
297  ocean_sfc_type, &
298  ocean_ice_type, &
299  ocean_alb_type, &
301  use mod_ocean_vars, only: &
302  ice_flag, &
303  ocean_temp, &
304  ocean_ocn_z0m, &
305  ocean_ice_temp, &
306  ocean_ice_mass, &
307  ocean_sfc_temp, &
309  ocean_sfc_z0m, &
310  ocean_sfc_z0h, &
311  ocean_sfc_z0e, &
312  ocean_temp_t, &
313  ocean_salt_t, &
314  ocean_uvel_t, &
315  ocean_vvel_t, &
318  atmos_temp, &
319  atmos_pres, &
320  atmos_u, &
321  atmos_v, &
322  atmos_dens, &
323  atmos_qv, &
324  atmos_pbl, &
325  atmos_cossza, &
326  atmos_sfc_dens, &
327  atmos_sfc_pres, &
330  atmos_sflx_engi, &
331  ocean_sflx_mw, &
332  ocean_sflx_mu, &
333  ocean_sflx_mv, &
334  ocean_sflx_sh, &
335  ocean_sflx_lh, &
336  ocean_sflx_qtrc, &
337  ocean_u10, &
338  ocean_v10, &
339  ocean_t2, &
340  ocean_q2, &
341  ocean_ustar, &
342  ocean_tstar, &
343  ocean_qstar, &
344  ocean_wstar, &
345  ocean_rlmo, &
346  ocean_ocn_ustar, &
347  ocean_ocn_tstar, &
348  ocean_ocn_qstar, &
349  ocean_ocn_wstar, &
350  ocean_ocn_rlmo, &
351  ocean_ice_ustar, &
352  ocean_ice_tstar, &
353  ocean_ice_qstar, &
354  ocean_ice_wstar, &
355  ocean_ice_rlmo, &
356  ocean_sflx_gh, &
358  ocean_sflx_engi, &
359  ocean_oflx_gh, &
361  ocean_oflx_engi, &
363  use scale_file_history, only: &
364  file_history_in
365  implicit none
366 
367  logical, intent(in) :: force
368 
369  real(rp) :: lhv (oia,oja)
370  real(rp) :: lhs (oia,oja)
371  real(rp) :: atmos_uabs (oia,oja)
372  real(rp) :: sfc_temp (oia,oja)
373  real(rp) :: sfc_albedo (oia,oja,n_rad_dir,n_rad_rgn)
374  real(rp) :: sfc_z0m (oia,oja)
375  real(rp) :: sfc_z0h (oia,oja)
376  real(rp) :: sfc_z0e (oia,oja)
377  real(rp) :: subsfc_temp (oia,oja)
378  real(rp) :: tc_dz (oia,oja)
379  real(rp) :: sflx_mw (oia,oja)
380  real(rp) :: sflx_mu (oia,oja)
381  real(rp) :: sflx_mv (oia,oja)
382  real(rp) :: sflx_sh (oia,oja)
383  real(rp) :: sflx_lh (oia,oja)
384  real(rp) :: sflx_qv (oia,oja)
385  real(rp) :: ocean_sflx_qv(oia,oja)
386  real(rp) :: u10 (oia,oja)
387  real(rp) :: v10 (oia,oja)
388  real(rp) :: t2 (oia,oja)
389  real(rp) :: q2 (oia,oja)
390  real(rp) :: sflx_hbalance(oia,oja)
391  real(rp) :: sflx_gh (oia,oja)
392  real(rp) :: sflx_water (oia,oja)
393  real(rp) :: sflx_engi (oia,oja)
394  real(rp) :: ice_mass (oia,oja)
395  logical :: exists_ice (oia,oja)
396  real(rp) :: sw
397 
398  real(rp) :: sfc_frac
399 
400  integer :: k, i, j, iq, idir, irgn
401  !---------------------------------------------------------------------------
402 
403  call prof_rapstart('OCN_CalcTend', 1)
404 
405  !$acc data create(LHV,LHS,ATMOS_Uabs,sfc_temp,sfc_albedo,sfc_Z0M,sfc_Z0H,sfc_Z0E,subsfc_temp,TC_dz, &
406  !$acc sflx_MW,sflx_MU,sflx_MV,sflx_SH,sflx_LH,sflx_QV,OCEAN_SFLX_QV,U10,V10,T2,Q2, &
407  !$acc sflx_hbalance,sflx_GH,sflx_water,sflx_engi,ice_mass,exists_ice)
408 
409  !########## Get Surface Boundary from coupler ##########
410  call ocean_surface_get
411 
412  !$omp parallel do
413  !$acc kernels
414  do j = ojs, oje
415  do i = ois, oie
416  atmos_uabs(i,j) = sqrt( atmos_u(i,j)**2 + atmos_v(i,j)**2 )
417  enddo
418  enddo
419  !$acc end kernels
420 
421  !$omp parallel do
422  !$acc kernels
423  do j = ojs, oje
424  do i = ois, oie
425  exists_ice(i,j) = .false.
426  if( exists_ocean(i,j) .AND. ocean_ice_frac(i,j) > 0.0_rp ) exists_ice(i,j) = .true.
427  enddo
428  enddo
429  !$acc end kernels
430 
431  !########## reset tendencies ##########
432 
433  !$omp parallel do
434  !$acc kernels
435  do j = ojs, oje
436  do i = ois, oie
437  do k = oks, oke
438  ocean_temp_t(k,i,j) = 0.0_rp
439  ocean_salt_t(k,i,j) = 0.0_rp
440  ocean_uvel_t(k,i,j) = 0.0_rp
441  ocean_vvel_t(k,i,j) = 0.0_rp
442  enddo
443  enddo
444  enddo
445  !$acc end kernels
446 
447  !$omp parallel do
448  !$acc kernels
449  do iq = 1, qa
450  do j = ojs, oje
451  do i = ois, oie
452  ocean_sflx_qtrc(i,j,iq) = 0.0_rp
453  enddo
454  enddo
455  enddo
456  !$acc end kernels
457 
458  if ( ice_flag ) then
459  !$omp parallel do
460  !$acc kernels
461  do j = ojs, oje
462  do i = ois, oie
463  ocean_ice_temp_t(i,j) = 0.0_rp
464  ocean_ice_mass_t(i,j) = 0.0_rp
465  enddo
466  enddo
467  !$acc end kernels
468  end if
469 
470 
471 
472  !########## surface process (ice-free ocean) ##########
473 
474  !$omp parallel do
475  !$acc kernels
476  do j = ojs, oje
477  do i = ois, oie
478  ocean_sfc_temp(i,j) = ocean_temp(oks,i,j)
479  enddo
480  enddo
481  !$acc end kernels
482 
483  ! albedo
484  select case ( ocean_alb_type )
485  case ( 'NAKAJIMA00' )
486  ! for Near-IR, IR
487  call ocean_phy_albedo_const ( oia, ois, oie, & ! [IN]
488  oja, ojs, oje, & ! [IN]
489  sfc_albedo(:,:,:,:) ) ! [OUT]
490  ! for VIS (overwrite)
491  call ocean_phy_albedo_nakajima00( oia, ois, oie, & ! [IN]
492  oja, ojs, oje, & ! [IN]
493  atmos_cossza(:,:), & ! [IN]
494  sfc_albedo(:,:,:,i_r_vis) ) ! [OUT]
495  case ( 'CONST' )
496  call ocean_phy_albedo_const ( oia, ois, oie, & ! [IN]
497  oja, ojs, oje, & ! [IN]
498  sfc_albedo(:,:,:,:) ) ! [OUT]
499  case ( 'INIT' )
500  ! Never update OCEAN_SFC_albedo from initial condition
501  !$omp parallel do
502  !$acc kernels
503  do irgn = i_r_ir, i_r_vis
504  do idir = i_r_direct, i_r_diffuse
505  do j = ojs, oje
506  do i = ois, oie
507  if ( exists_ocean(i,j) ) then
508  sfc_albedo(i,j,idir,irgn) = ocean_sfc_albedo(i,j,idir,irgn)
509  end if
510  enddo
511  enddo
512  enddo
513  enddo
514  !$acc end kernels
515  end select
516 
517  ! roughness length
518  select case ( ocean_rgn_type )
519  case ( 'MILLER92' )
520  call ocean_phy_roughness_miller92( oia, ois, oie, & ! [IN]
521  oja, ojs, oje, & ! [IN]
522  atmos_uabs(:,:), & ! [IN]
523  ocean_ocn_z0m(:,:), & ! [OUT]
524  ocean_sfc_z0h(:,:), & ! [OUT]
525  ocean_sfc_z0e(:,:) ) ! [OUT]
526  case ( 'MOON07' )
527  call ocean_phy_roughness_moon07 ( oia, ois, oie, & ! [IN]
528  oja, ojs, oje, & ! [IN]
529  atmos_uabs(:,:), & ! [IN]
530  real_z1(:,:), & ! [IN]
531  exists_ocean(:,:), & ! [IN]
532  ocean_ocn_z0m(:,:), & ! [INOUT]
533  ocean_sfc_z0h(:,:), & ! [OUT]
534  ocean_sfc_z0e(:,:) ) ! [OUT]
535  case ( 'CONST' )
536  call ocean_phy_roughness_const ( oia, ois, oie, & ! [IN]
537  oja, ojs, oje, & ! [IN]
538  ocean_ocn_z0m(:,:), & ! [OUT]
539  ocean_sfc_z0h(:,:), & ! [OUT]
540  ocean_sfc_z0e(:,:) ) ! [OUT]
541  case ( 'INIT' )
542  ! Never update from initial condition
543  end select
544 
545  ! tendency
546  select case ( ocean_sfc_type )
547  case ( 'FIXED-TEMP' )
548 
549  call hydrometeor_lhv( oia, ois, oie, oja, ojs, oje, & ! [IN]
550  ocean_sfc_temp(:,:), & ! [IN]
551  lhv(:,:) ) ! [OUT]
552 
553  call cpl_phy_sfc_fixed_temp( oia, ois, oie, & ! [IN]
554  oja, ojs, oje, & ! [IN]
555  atmos_temp(:,:), & ! [IN]
556  atmos_pres(:,:), & ! [IN]
557  atmos_w(:,:), & ! [IN]
558  atmos_u(:,:), & ! [IN]
559  atmos_v(:,:), & ! [IN]
560  atmos_dens(:,:), & ! [IN]
561  atmos_qv(:,:), & ! [IN]
562  lhv(:,:), & ! [IN]
563  real_z1(:,:), & ! [IN]
564  atmos_pbl(:,:), & ! [IN]
565  atmos_sfc_dens(:,:), & ! [IN]
566  atmos_sfc_pres(:,:), & ! [IN]
567  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
568  ocean_sfc_temp(:,:), & ! [IN]
569  wstr(:,:), & ! [IN]
570  qvef(:,:), & ! [IN]
571  sfc_albedo(:,:,:,:), & ! [IN]
572  sr(:,:), & ! [IN]
573  ocean_ocn_z0m(:,:), & ! [IN]
574  ocean_sfc_z0h(:,:), & ! [IN]
575  ocean_sfc_z0e(:,:), & ! [IN]
576  exists_ocean(:,:), & ! [IN]
577  dt, & ! [IN]
578  ocean_sflx_mw(:,:), & ! [OUT]
579  ocean_sflx_mu(:,:), & ! [OUT]
580  ocean_sflx_mv(:,:), & ! [OUT]
581  ocean_sflx_sh(:,:), & ! [OUT]
582  ocean_sflx_lh(:,:), & ! [OUT]
583  ocean_sflx_qv(:,:), & ! [OUT]
584  ocean_sflx_gh(:,:), & ! [OUT]
585  ocean_ocn_ustar(:,:), & ! [OUT]
586  ocean_ocn_tstar(:,:), & ! [OUT]
587  ocean_ocn_qstar(:,:), & ! [OUT]
588  ocean_ocn_wstar(:,:), & ! [OUT]
589  ocean_ocn_rlmo(:,:), & ! [OUT]
590  ocean_u10(:,:), & ! [OUT]
591  ocean_v10(:,:), & ! [OUT]
592  ocean_t2(:,:), & ! [OUT]
593  ocean_q2(:,:) ) ! [OUT]
594  end select
595 
596  !$omp parallel do
597  !$acc kernels
598  !$acc loop independent
599  do j = ojs, oje
600  !$acc loop independent
601  do i = ois, oie
602  if ( exists_ocean(i,j) ) then
603  ocean_sflx_water(i,j) = atmos_sflx_water(i,j) - ocean_sflx_qv(i,j)
604  ocean_sflx_engi(i,j) = atmos_sflx_engi(i,j) & ! internal energy of precipitation
605  - ocean_sflx_qv(i,j) * cv_water * ocean_sfc_temp(i,j) ! internal energy of evaporation water
606  end if
607  enddo
608  enddo
609  !$acc end kernels
610 
611  ! weighted average
612 
613  if ( ice_flag ) then
614 
615  ! history (open ocean)
616  call file_history_in( ocean_u10(:,:), 'OCEAN_OCN_U10', 'Wind velocity u at 10 m on open ocean surface', 'm/s' )
617  call file_history_in( ocean_v10(:,:), 'OCEAN_OCN_V10', 'Wind velocity v at 10 m on open ocean surface', 'm/s' )
618  call file_history_in( ocean_t2(:,:), 'OCEAN_OCN_T2', 'Air temperature at 2m on open ocean surface', 'K' )
619  call file_history_in( ocean_q2(:,:), 'OCEAN_OCN_Q2', 'Specific humidity at 2m on open ocean surface', 'kg/kg' )
620 
621  !$omp parallel do &
622  !$omp private(sfc_frac)
623  !$acc kernels
624  !$acc loop independent
625  do j = ojs, oje
626  !$acc loop independent
627  do i = ois, oie
628  if ( exists_ocean(i,j) ) then
629  sfc_frac = 1.0_rp - ocean_ice_frac(i,j)
630 
631  ocean_sfc_temp(i,j) = ocean_sfc_temp(i,j) * sfc_frac
632  ocean_sfc_z0m(i,j) = ocean_ocn_z0m(i,j) * sfc_frac
633  ocean_sfc_z0h(i,j) = ocean_sfc_z0h(i,j) * sfc_frac
634  ocean_sfc_z0e(i,j) = ocean_sfc_z0e(i,j) * sfc_frac
635  ocean_sflx_mw(i,j) = ocean_sflx_mw(i,j) * sfc_frac
636  ocean_sflx_mu(i,j) = ocean_sflx_mu(i,j) * sfc_frac
637  ocean_sflx_mv(i,j) = ocean_sflx_mv(i,j) * sfc_frac
638  ocean_sflx_sh(i,j) = ocean_sflx_sh(i,j) * sfc_frac
639  ocean_sflx_lh(i,j) = ocean_sflx_lh(i,j) * sfc_frac
640  ocean_sflx_qv(i,j) = ocean_sflx_qv(i,j) * sfc_frac
641  ocean_u10(i,j) = ocean_u10(i,j) * sfc_frac
642  ocean_v10(i,j) = ocean_v10(i,j) * sfc_frac
643  ocean_t2(i,j) = ocean_t2(i,j) * sfc_frac
644  ocean_q2(i,j) = ocean_q2(i,j) * sfc_frac
645 
646  ocean_sflx_gh(i,j) = ocean_sflx_gh(i,j) * sfc_frac
647  ocean_sflx_water(i,j) = ocean_sflx_water(i,j) * sfc_frac
648  ocean_sflx_engi(i,j) = ocean_sflx_engi(i,j) * sfc_frac
649 
650  do irgn = i_r_ir, i_r_vis
651  do idir = i_r_direct, i_r_diffuse
652  ocean_sfc_albedo(i,j,idir,irgn) = sfc_albedo(i,j,idir,irgn) * sfc_frac
653  enddo
654  enddo
655  end if
656  enddo
657  enddo
658  !$acc end kernels
659 
660  end if
661 
662 
663  !########## surface process (ice) ##########
664 
665  if ( ice_flag ) then
666 
667  !$omp parallel do
668  !$acc kernels
669  do j = ojs, oje
670  do i = ois, oie
671  subsfc_temp(i,j) = ocean_temp(oks,i,j)
672  enddo
673  enddo
674  !$acc end kernels
675 
676  ! albedo
677  select case ( ocean_alb_type )
678  case ( 'NAKAJIMA00' )
679  call ocean_phy_albedo_seaice( oia, ois, oie, & ! [IN]
680  oja, ojs, oje, & ! [IN]
681  sfc_albedo(:,:,:,:) ) ! [OUT]
682  case ( 'CONST' )
683  call ocean_phy_albedo_const ( oia, ois, oie, & ! [IN]
684  oja, ojs, oje, & ! [IN]
685  sfc_albedo(:,:,:,:) ) ! [OUT]
686  case ( 'INIT' )
687  ! Never update OCEAN_SFC_albedo from initial condition
688  !$omp parallel do
689  !$acc kernels
690  do irgn = i_r_ir, i_r_vis
691  do idir = i_r_direct, i_r_diffuse
692  do j = ojs, oje
693  do i = ois, oie
694  sfc_albedo(i,j,idir,irgn) = ocean_sfc_albedo(i,j,idir,irgn)
695  enddo
696  enddo
697  enddo
698  enddo
699  !$acc end kernels
700  end select
701 
702  ! roughness length
703  select case ( ocean_rgn_type )
704  case ( 'MILLER92', 'MOON07' )
705  call ocean_phy_roughness_seaice( oia, ois, oie, & ! [IN]
706  oja, ojs, oje, & ! [IN]
707  sfc_z0m(:,:), & ! [OUT]
708  sfc_z0h(:,:), & ! [OUT]
709  sfc_z0e(:,:) ) ! [OUT]
710  case ( 'CONST' )
711  call ocean_phy_roughness_const ( oia, ois, oie, & ! [IN]
712  oja, ojs, oje, & ! [IN]
713  sfc_z0m(:,:), & ! [OUT]
714  sfc_z0h(:,:), & ! [OUT]
715  sfc_z0e(:,:) ) ! [OUT]
716  case ( 'INIT' )
717  ! Never update OCEAN_SFC_Z0M/H/E from initial condition
718  !$omp parallel do
719  !$acc kernels
720  do j = ojs, oje
721  do i = ois, oie
722  sfc_z0m(i,j) = ocean_sfc_z0m(i,j)
723  sfc_z0h(i,j) = ocean_sfc_z0h(i,j)
724  sfc_z0e(i,j) = ocean_sfc_z0e(i,j)
725  enddo
726  enddo
727  !$acc end kernels
728  end select
729 
730  ! thermal conductivity / depth
731  call ocean_phy_tc_seaice( oia, ois, oie, & ! [IN]
732  oja, ojs, oje, & ! [IN]
733  ocean_ice_mass(:,:), & ! [IN]
734  ocean_ice_frac(:,:), & ! [IN]
735  exists_ice(:,:), & ! [IN]
736  tc_dz(:,:) ) ! [OUT]
737 
738  ! tendency
739  select case ( ocean_sfc_type )
740  case ( 'FIXED-TEMP' )
741  !$omp parallel do private(sw)
742  !$acc kernels
743  do j = ojs, oje
744  do i = ois, oie
745  if ( exists_ocean(i,j) ) then
746  sw = 0.5_rp + sign(0.5_rp, ocean_ice_frac(i,j)-eps)
747  ice_mass(i,j) = ocean_ice_mass(i,j) * sw / ( ocean_ice_frac(i,j) + 1.0_rp - sw )
748  end if
749  end do
750  end do
751  !$acc end kernels
752 
753  call hydrometeor_lhs( oia, ois, oie, oja, ojs, oje, & ! [IN]
754  ocean_ice_temp(:,:), & ! [IN]
755  lhs(:,:) ) ! [OUT]
756 
757  call cpl_phy_sfc_fixed_temp( oia, ois, oie, & ! [IN]
758  oja, ojs, oje, & ! [IN]
759  atmos_temp(:,:), & ! [IN]
760  atmos_pres(:,:), & ! [IN]
761  atmos_w(:,:), & ! [IN]
762  atmos_u(:,:), & ! [IN]
763  atmos_v(:,:), & ! [IN]
764  atmos_dens(:,:), & ! [IN]
765  atmos_qv(:,:), & ! [IN]
766  lhs(:,:), & ! [IN]
767  real_z1(:,:), & ! [IN]
768  atmos_pbl(:,:), & ! [IN]
769  atmos_sfc_dens(:,:), & ! [IN]
770  atmos_sfc_pres(:,:), & ! [IN]
771  atmos_sflx_rad_dn(:,:,:,:), & ! [IN]
772  ocean_ice_temp(:,:), & ! [IN]
773  ice_mass(:,:), & ! [IN]
774  qvef(:,:), & ! [IN]
775  sfc_albedo(:,:,:,:), & ! [IN]
776  sr(:,:), & ! [IN]
777  sfc_z0m(:,:), & ! [IN]
778  sfc_z0h(:,:), & ! [IN]
779  sfc_z0e(:,:), & ! [IN]
780  exists_ice(:,:), & ! [IN]
781  dt, & ! [IN]
782  sflx_mw(:,:), & ! [OUT]
783  sflx_mu(:,:), & ! [OUT]
784  sflx_mv(:,:), & ! [OUT]
785  sflx_sh(:,:), & ! [OUT]
786  sflx_lh(:,:), & ! [OUT]
787  sflx_qv(:,:), & ! [OUT]
788  sflx_gh(:,:), & ! [OUT]
789  ocean_ice_ustar(:,:), & ! [OUT]
790  ocean_ice_tstar(:,:), & ! [OUT]
791  ocean_ice_qstar(:,:), & ! [OUT]
792  ocean_ice_wstar(:,:), & ! [OUT]
793  ocean_ice_rlmo(:,:), & ! [OUT]
794  u10(:,:), & ! [OUT]
795  v10(:,:), & ! [OUT]
796  t2(:,:), & ! [OUT]
797  q2(:,:) ) ! [OUT]
798  end select
799 
800  !$omp parallel do
801  !$acc kernels
802  do j = ojs, oje
803  do i = ois, oie
804  if ( exists_ocean(i,j) ) then
805  sflx_water(i,j) = atmos_sflx_water(i,j) - sflx_qv(i,j)
806  sflx_engi(i,j) = atmos_sflx_engi(i,j) & ! internal energy of precipitation
807  - sflx_qv(i,j) * ( cv_ice * ocean_ice_temp(i,j) - lhf ) ! internal energy of evaporation water
808  end if
809  enddo
810  enddo
811  !$acc end kernels
812 
813  ! weighted average
814  !$omp parallel do
815  !$acc kernels
816  !$acc loop independent
817  do j = ojs, oje
818  !$acc loop independent
819  do i = ois, oie
820  if ( exists_ocean(i,j) ) then
822  ocean_sfc_z0m(i,j) = ocean_sfc_z0m(i,j) + sfc_z0m(i,j) * ocean_ice_frac(i,j)
823  ocean_sfc_z0h(i,j) = ocean_sfc_z0h(i,j) + sfc_z0h(i,j) * ocean_ice_frac(i,j)
824  ocean_sfc_z0e(i,j) = ocean_sfc_z0e(i,j) + sfc_z0e(i,j) * ocean_ice_frac(i,j)
825  ocean_sflx_mw(i,j) = ocean_sflx_mw(i,j) + sflx_mw(i,j) * ocean_ice_frac(i,j)
826  ocean_sflx_mu(i,j) = ocean_sflx_mu(i,j) + sflx_mu(i,j) * ocean_ice_frac(i,j)
827  ocean_sflx_mv(i,j) = ocean_sflx_mv(i,j) + sflx_mv(i,j) * ocean_ice_frac(i,j)
828  ocean_sflx_sh(i,j) = ocean_sflx_sh(i,j) + sflx_sh(i,j) * ocean_ice_frac(i,j)
829  ocean_sflx_qv(i,j) = ocean_sflx_qv(i,j) + sflx_qv(i,j) * ocean_ice_frac(i,j)
830  ocean_sflx_lh(i,j) = ocean_sflx_lh(i,j) + sflx_lh(i,j) * ocean_ice_frac(i,j)
831  ocean_u10(i,j) = ocean_u10(i,j) + u10(i,j) * ocean_ice_frac(i,j)
832  ocean_v10(i,j) = ocean_v10(i,j) + v10(i,j) * ocean_ice_frac(i,j)
833  ocean_t2(i,j) = ocean_t2(i,j) + t2(i,j) * ocean_ice_frac(i,j)
834  ocean_q2(i,j) = ocean_q2(i,j) + q2(i,j) * ocean_ice_frac(i,j)
835 
836  ocean_oflx_gh(i,j) = ocean_sflx_gh(i,j)
838  ocean_oflx_engi(i,j) = ocean_sflx_engi(i,j)
839 
840  ocean_sflx_gh(i,j) = ocean_sflx_gh(i,j) + sflx_gh(i,j) * ocean_ice_frac(i,j)
841  ocean_sflx_water(i,j) = ocean_sflx_water(i,j) + sflx_water(i,j) * ocean_ice_frac(i,j)
842  ocean_sflx_engi(i,j) = ocean_sflx_engi(i,j) + sflx_engi(i,j) * ocean_ice_frac(i,j)
843  end if
844  end do
845  end do
846  !$acc end kernels
847 
848  !$omp parallel do
849  !$acc kernels
850  do irgn = i_r_ir, i_r_vis
851  do idir = i_r_direct, i_r_diffuse
852  do j = ojs, oje
853  do i = ois, oie
854  if ( exists_ocean(i,j) ) then
855  ocean_sfc_albedo(i,j,idir,irgn) = ocean_sfc_albedo(i,j,idir,irgn) + sfc_albedo(i,j,idir,irgn) * ocean_ice_frac(i,j)
856  end if
857  enddo
858  enddo
859  enddo
860  enddo
861  !$acc end kernels
862 
863 
864  ! seaice
865  select case ( ocean_ice_type )
866  case ( 'SIMPLE' )
867 
868  !$omp parallel do
869  !$acc kernels
870  do j = ojs, oje
871  do i = ois, oie
872  if ( exists_ocean(i,j) ) then
873  sflx_hbalance(i,j) = sflx_gh(i,j) + sflx_engi(i,j)
874  end if
875  enddo
876  enddo
877  !$acc end kernels
878 
879  call ocean_phy_ice_simple( oia, ois, oie, & ! [IN]
880  oja, ojs, oje, & ! [IN]
881  sflx_water(:,:), & ! [IN]
882  sflx_hbalance(:,:), & ! [IN]
883  subsfc_temp(:,:), & ! [IN]
884  tc_dz(:,:), & ! [IN]
885  ocean_ice_temp(:,:), & ! [IN]
886  ocean_ice_mass(:,:), & ! [IN]
887  ocean_ice_frac(:,:), & ! [IN]
888  exists_ice(:,:), & ! [IN]
889  dt, & ! [IN]
890  ocean_ice_temp_t(:,:), & ! [OUT]
891  ocean_ice_mass_t(:,:), & ! [OUT]
892  sflx_gh(:,:), & ! [OUT]
893  sflx_water(:,:), & ! [OUT]
894  sflx_engi(:,:) ) ! [OUT]
895  case ( 'INIT' )
896  !$omp parallel do
897  !$acc kernels
898  do j = ojs, oje
899  do i = ois, oie
900  if ( exists_ocean(i,j) ) then
901  sflx_gh(i,j) = sflx_gh(i,j) * ocean_ice_frac(i,j)
902  sflx_water(i,j) = 0.0_rp ! no flux from seaice to ocean
903  sflx_engi(i,j) = 0.0_rp ! no flux from seaice to ocean
904  end if
905  enddo
906  enddo
907  !$acc end kernels
908  end select
909 
910  ! history (sea ice)
911  call file_history_in( u10(:,:), 'OCEAN_ICE_U10', 'Wind velocity u at 10 m on sea ice surface', 'm/s' )
912  call file_history_in( v10(:,:), 'OCEAN_ICE_V10', 'Wind velocity v at 10 m on sea ice surface', 'm/s' )
913  call file_history_in( t2(:,:), 'OCEAN_ICE_T2', 'Air temperature at 2m on sea ice surface', 'K' )
914  call file_history_in( q2(:,:), 'OCEAN_ICE_Q2', 'Specific humidity at 2m on sea ice surface', 'kg/kg' )
915 
916  ! weighted average
917  !$omp parallel do
918  !$acc kernels
919  !$acc loop independent
920  do j = ojs, oje
921  !$acc loop independent
922  do i = ois, oie
923  if ( exists_ocean(i,j) ) then
924  ocean_oflx_gh(i,j) = ocean_oflx_gh(i,j) + sflx_gh(i,j)
925  ocean_oflx_water(i,j) = ocean_oflx_water(i,j) + sflx_water(i,j)
926  ocean_oflx_engi(i,j) = ocean_oflx_engi(i,j) + sflx_engi(i,j)
927  end if
928  enddo
929  enddo
930  !$acc end kernels
931 
932  call bulkflux_diagnose_scales( oia, ois, oie, oja, ojs, oje, &
933  ocean_sflx_mw(:,:), ocean_sflx_mu(:,:), ocean_sflx_mv(:,:), & ! [IN]
934  ocean_sflx_sh(:,:), ocean_sflx_qv(:,:), & ! [IN]
935  atmos_sfc_dens(:,:), ocean_sfc_temp(:,:), atmos_pbl(:,:), & ! [IN]
936  ocean_ustar(:,:), ocean_tstar(:,:), ocean_qstar(:,:), & ! [OUT]
937  ocean_wstar(:,:), ocean_rlmo(:,:), & ! [OUT]
938  mask = exists_ocean(:,:) ) ! [IN]
939 
940 
941 
942 
943  endif ! ICE process?
944 
945  if ( .NOT. atmos_hydrometeor_dry ) then
946  !$omp parallel do
947  !$acc kernels
948  do j = ojs, oje
949  do i = ois, oie
950  if ( exists_ocean(i,j) ) then
951  ocean_sflx_qtrc(i,j,i_qv) = ocean_sflx_qv(i,j)
952  end if
953  enddo
954  enddo
955  !$acc end kernels
956  endif
957 
958 
959  ! Surface flux for chemical tracers
960  if ( atmos_sw_phy_ch ) then
961  call atmos_phy_ch_driver_ocean_flux( ocean_sflx_qtrc(:,:,:) ) ! [INOUT]
962  endif
963 
964  if ( statistics_checktotal ) then
965  call statistics_total( oka, oks, oke, oia, ois, oie, oja, ojs, oje, &
966  ocean_temp_t(:,:,:), 'OCEAN_TEMP_t', &
967  ocean_grid_cartesc_real_vol(:,:,:), &
968  ocean_grid_cartesc_real_totvol )
969  if ( ice_flag ) then
970  call statistics_total( oia, ois, oie, oja, ojs, oje, &
971  ocean_ice_temp_t(:,:), 'OCEAN_ICE_TEMP_t', &
974  call statistics_total( oia, ois, oie, oja, ojs, oje, &
975  ocean_ice_mass_t(:,:), 'OCEAN_ICE_MASS_t', &
978  end if
979  endif
980 
981  !########## Set Surface Boundary to coupler ##########
982  call ocean_surface_set( countup=.true. )
983 
984  !$acc end data
985 
986  call prof_rapend ('OCN_CalcTend', 1)
987 
988  return
989  end subroutine ocean_driver_calc_tendency
990 
991  !-----------------------------------------------------------------------------
993  subroutine ocean_driver_update
994  use scale_time, only: &
995  nowdaysec => time_nowdaysec, &
996  dt => time_dtsec_ocean
997  use scale_landuse, only: &
998  exists_ocean => landuse_exists_ocean
999  use mod_ocean_admin, only: &
1000  ocean_dyn_type, &
1002  use mod_ocean_vars, only: &
1003  ocean_temp, &
1004  ocean_salt, &
1005  ocean_uvel, &
1006  ocean_vvel, &
1007  ocean_ice_temp, &
1008  ocean_ice_mass, &
1009  ocean_ice_frac, &
1010  ocean_temp_t, &
1011  ocean_salt_t, &
1012  ocean_uvel_t, &
1013  ocean_vvel_t, &
1014  ocean_ice_temp_t, &
1015  ocean_ice_mass_t, &
1016  ocean_oflx_gh, &
1017  ocean_oflx_water, &
1018  ocean_oflx_engi, &
1019  ocean_mass_supl, &
1020  ocean_engi_supl, &
1022  use scale_ocean_dyn_slab, only: &
1024  use scale_ocean_dyn_offline, only: &
1026  use scale_ocean_phy_ice_simple, only: &
1029  use scale_ocean_grid_cartesc, only: &
1030  cdz => ocean_grid_cartesc_cdz
1031  implicit none
1032 
1033  real(rp) :: mass_flux(oia,oja)
1034  real(rp) :: engi_flux(oia,oja)
1035  real(rp) :: mass_supl(oia,oja)
1036  real(rp) :: engi_supl(oia,oja)
1037 
1038  real(rp) :: sflx_gh(oia,oja)
1039 
1040  real(rp) :: ocean_temp_ks(oia,oja)
1041 
1042  integer :: i, j
1043  !---------------------------------------------------------------------------
1044 
1045  call prof_rapstart('OCN_Update', 1)
1046 
1047  !$acc data create(MASS_FLUX,ENGI_FLUX,MASS_SUPL,ENGI_SUPL)
1048 
1049  !########## Get Surface Boundary from coupler ##########
1050  call ocean_surface_get
1051 
1052  !########## Dynamics / Update ##########
1053  !$omp parallel do
1054  !$acc kernels
1055  do j = ojs, oje
1056  do i = ois, oie
1057  ocean_mass_supl(i,j) = 0.0_rp
1058  ocean_engi_supl(i,j) = 0.0_rp
1059  end do
1060  end do
1061  !$acc end kernels
1062 
1063  select case ( ocean_dyn_type )
1064  case ( 'SLAB' )
1065 
1066  !$omp parallel do
1067  !$acc kernels
1068  do j = ojs, oje
1069  do i = ois, oie
1070  if ( exists_ocean(i,j) ) then
1071  sflx_gh(i,j) = ocean_oflx_gh(i,j) + ocean_oflx_engi(i,j)
1072  end if
1073  end do
1074  end do
1075  !$acc end kernels
1076 
1077  call ocean_dyn_slab( okmax, oks, oke, & ! [IN]
1078  oia, ois, oie, & ! [IN]
1079  oja, ojs, oje, & ! [IN]
1080  ocean_temp_t(:,:,:), & ! [IN]
1081  sflx_gh(:,:), & ! [IN]
1082  ocean_oflx_water(:,:), & ! [IN]
1083  exists_ocean(:,:), & ! [IN]
1084  dt, nowdaysec, & ! [IN]
1085  ocean_temp(:,:,:), & ! [INOUT]
1086  mass_supl(:,:), & ! [OUT]
1087  engi_supl(:,:) ) ! [OUT]
1088 
1089  !$omp parallel do
1090  !$acc kernels
1091  do j = ojs, oje
1092  do i = ois, oie
1093  if ( exists_ocean(i,j) ) then
1094  ocean_mass_supl(i,j) = ocean_mass_supl(i,j) + mass_supl(i,j)
1095  ocean_engi_supl(i,j) = ocean_engi_supl(i,j) + engi_supl(i,j)
1096  end if
1097  end do
1098  end do
1099  !$acc end kernels
1100 
1101  case ( 'OFFLINE' )
1102 
1103  call ocean_dyn_offline( okmax, oks, oke, & ! [IN]
1104  oia, ois, oie, & ! [IN]
1105  oja, ojs, oje, & ! [IN]
1106  exists_ocean(:,:), & ! [IN]
1107  dt, nowdaysec, & ! [IN]
1108  ocean_temp(:,:,:) ) ! [INOUT]
1109 
1110  case ( 'INIT' )
1111  ! Never update OCEAN_TEMP from initial condition
1112  end select
1113 
1114  !########## Ice / Update ##########
1115  select case ( ocean_ice_type )
1116  case ( 'SIMPLE' )
1117 
1118  !$omp parallel do
1119  !$acc kernels
1120  do j = ojs, oje
1121  do i = ois, oie
1122  if ( exists_ocean(i,j) ) then
1123  ocean_ice_temp(i,j) = ocean_ice_temp(i,j) + ocean_ice_temp_t(i,j) * dt
1124  ocean_ice_mass(i,j) = ocean_ice_mass(i,j) + ocean_ice_mass_t(i,j) * dt
1125  end if
1126  enddo
1127  enddo
1128  !$acc end kernels
1129 
1130  ! ice adjustment
1131  !$acc data create(OCEAN_TEMP_KS)
1132  !$omp parallel do
1133  !$acc kernels
1134  do j = ojs, oje
1135  do i = ois, oie
1136  ocean_temp_ks(i,j) = ocean_temp(oks,i,j)
1137  end do
1138  end do
1139  !$acc end kernels
1140  call ocean_phy_ice_adjustment( oia, ois, oie, & ! [IN]
1141  oja, ojs, oje, & ! [IN]
1142  exists_ocean(:,:), & ! [IN]
1143  cdz(oks), & ! [IN]
1144  ocean_temp_ks(:,:), & ! [INOUT]
1145  ocean_ice_temp(:,:), & ! [INOUT]
1146  ocean_ice_mass(:,:), & ! [INOUT]
1147  mass_flux(:,:), & ! [OUT]
1148  engi_flux(:,:), & ! [OUT]
1149  mass_supl(:,:), & ! [OUT]
1150  engi_supl(:,:) ) ! [OUT]
1151  !$omp parallel do
1152  !$acc kernels
1153  do j = ojs, oje
1154  do i = ois, oie
1155  ocean_temp(oks,i,j) = ocean_temp_ks(i,j)
1156  end do
1157  end do
1158  !$acc end kernels
1159  !$acc end data
1160 
1161  !$omp parallel do
1162  !$acc kernels
1163  !$acc loop independent
1164  do j = ojs, oje
1165  !$acc loop independent
1166  do i = ois, oie
1167  if ( exists_ocean(i,j) ) then
1168  ocean_oflx_water(i,j) = ocean_oflx_water(i,j) - mass_flux(i,j) / dt
1169  ocean_oflx_engi(i,j) = ocean_oflx_engi(i,j) - engi_flux(i,j) / dt
1170  ocean_mass_supl(i,j) = ocean_mass_supl(i,j) + mass_supl(i,j) / dt
1171  ocean_engi_supl(i,j) = ocean_engi_supl(i,j) + engi_supl(i,j) / dt
1172  end if
1173  end do
1174  end do
1175  !$acc end kernels
1176 
1177  ! update ice fraction
1178  call ocean_phy_ice_fraction( oia, ois, oie, & ! [IN]
1179  oja, ojs, oje, & ! [IN]
1180  ocean_ice_mass(:,:), & ! [IN]
1181  ocean_ice_frac(:,:) ) ! [OUT]
1182 
1183  case ( 'INIT' )
1184  ! Never update OCEAN_ICE_TEMP, OCEAN_ICE_MASS, OCEAN_ICE_FRAC from initial condition
1185  end select
1186 
1187  call ocean_vars_check
1188 
1189  !$acc end data
1190 
1191  call prof_rapend ('OCN_Update', 1)
1192 
1193  return
1194  end subroutine ocean_driver_update
1195 
1196  !-----------------------------------------------------------------------------
1198  subroutine ocean_surface_get
1199  use mod_ocean_admin, only: &
1200  ocean_do
1201  use mod_ocean_vars, only: &
1202  atmos_temp, &
1203  atmos_pres, &
1204  atmos_w, &
1205  atmos_u, &
1206  atmos_v, &
1207  atmos_dens, &
1208  atmos_qv, &
1209  atmos_pbl, &
1210  atmos_sfc_dens, &
1211  atmos_sfc_pres, &
1213  atmos_cossza, &
1214  atmos_sflx_water, &
1216  use mod_cpl_vars, only: &
1218  implicit none
1219  !---------------------------------------------------------------------------
1220 
1221  call prof_rapstart('OCN_SfcExch', 3)
1222 
1223  if ( ocean_do ) then
1224  call cpl_getatm_ocn( atmos_temp(:,:), & ! [OUT]
1225  atmos_pres(:,:), & ! [OUT]
1226  atmos_w(:,:), & ! [OUT]
1227  atmos_u(:,:), & ! [OUT]
1228  atmos_v(:,:), & ! [OUT]
1229  atmos_dens(:,:), & ! [OUT]
1230  atmos_qv(:,:), & ! [OUT]
1231  atmos_pbl(:,:), & ! [OUT]
1232  atmos_sfc_dens(:,:), & ! [OUT]
1233  atmos_sfc_pres(:,:), & ! [OUT]
1234  atmos_sflx_rad_dn(:,:,:,:), & ! [OUT]
1235  atmos_cossza(:,:), & ! [OUT]
1236  atmos_sflx_water(:,:), & ! [OUT]
1237  atmos_sflx_engi(:,:) ) ! [OUT]
1238  endif
1239 
1240  call prof_rapend ('OCN_SfcExch', 3)
1241 
1242  return
1243  end subroutine ocean_surface_get
1244 
1245  !-----------------------------------------------------------------------------
1247  subroutine ocean_surface_set( countup )
1248  use mod_ocean_admin, only: &
1249  ocean_do
1250  use mod_ocean_vars, only: &
1251  ocean_sfc_temp, &
1252  ocean_sfc_albedo, &
1253  ocean_sfc_z0m, &
1254  ocean_sfc_z0h, &
1255  ocean_sfc_z0e, &
1256  ocean_sflx_mw, &
1257  ocean_sflx_mu, &
1258  ocean_sflx_mv, &
1259  ocean_sflx_sh, &
1260  ocean_sflx_lh, &
1261  ocean_sflx_qtrc, &
1262  ocean_u10, &
1263  ocean_v10, &
1264  ocean_t2, &
1265  ocean_q2, &
1267  use mod_cpl_vars, only: &
1268  cpl_putocn
1269  use scale_landuse, only: &
1270  exists_ocean => landuse_exists_ocean
1271  implicit none
1272 
1273  logical, intent(in) :: countup
1274  !---------------------------------------------------------------------------
1275 
1276  call prof_rapstart('OCN_SfcExch', 3)
1277 
1278  if ( ocean_do ) then
1279  call cpl_putocn( ocean_sfc_temp(:,:), & ! [IN]
1280  ocean_sfc_albedo(:,:,:,:), & ! [IN]
1281  ocean_sfc_z0m(:,:), & ! [IN]
1282  ocean_sfc_z0h(:,:), & ! [IN]
1283  ocean_sfc_z0e(:,:), & ! [IN]
1284  ocean_sflx_mw(:,:), & ! [IN]
1285  ocean_sflx_mu(:,:), & ! [IN]
1286  ocean_sflx_mv(:,:), & ! [IN]
1287  ocean_sflx_sh(:,:), & ! [IN]
1288  ocean_sflx_lh(:,:), & ! [IN]
1289  ocean_sflx_gh(:,:), & ! [IN]
1290  ocean_sflx_qtrc(:,:,:), & ! [IN]
1291  ocean_u10(:,:), & ! [IN]
1292  ocean_v10(:,:), & ! [IN]
1293  ocean_t2(:,:), & ! [IN]
1294  ocean_q2(:,:), & ! [IN]
1295  exists_ocean(:,:), & ! [IN]
1296  countup ) ! [IN]
1297  endif
1298 
1299  call prof_rapend ('OCN_SfcExch', 3)
1300 
1301  return
1302  end subroutine ocean_surface_set
1303 
1304 end module mod_ocean_driver
scale_cpl_sfc_index::n_rad_dir
integer, parameter, public n_rad_dir
Definition: scale_cpl_sfc_index.F90:36
mod_ocean_driver
module OCEAN driver
Definition: mod_ocean_driver.F90:11
scale_ocean_dyn_offline::ocean_dyn_offline_setup
subroutine, public ocean_dyn_offline_setup
Setup.
Definition: scale_ocean_dyn_offline.F90:48
scale_ocean_dyn_slab::ocean_dyn_slab
subroutine, public ocean_dyn_slab(OKMAX, OKS, OKE, OIA, OIS, OIE, OJA, OJS, OJE, OCEAN_TEMP_t, OCEAN_SFLX_G, OCEAN_SFLX_water, calc_flag, dt, NOWDAYSEC, OCEAN_TEMP, MASS_SUPL, ENGI_SUPL)
Slab ocean model.
Definition: scale_ocean_dyn_slab.F90:182
scale_statistics
module Statistics
Definition: scale_statistics.F90:11
mod_ocean_vars::ocean_ocn_z0m
real(rp), dimension(:,:), allocatable, public ocean_ocn_z0m
surface roughness length for momentum, open ocean [m]
Definition: mod_ocean_vars.F90:66
scale_ocean_phy_roughness::ocean_phy_roughness_seaice
subroutine, public ocean_phy_roughness_seaice(OIA, OIS, OIE, OJA, OJS, OJE, Z0M, Z0H, Z0E)
Definition: scale_ocean_phy_roughness.F90:192
mod_ocean_vars::ocean_sflx_mv
real(rp), dimension(:,:), allocatable, public ocean_sflx_mv
ocean surface v-momentum flux [kg/m/s2]
Definition: mod_ocean_vars.F90:114
scale_ocean_dyn_offline
module ocean / dynamics / offline
Definition: scale_ocean_dyn_offline.F90:12
scale_ocean_phy_albedo::ocean_phy_albedo_const
subroutine, public ocean_phy_albedo_const(OIA, OIS, OIE, OJA, OJS, OJE, SFC_albedo)
Definition: scale_ocean_phy_albedo.F90:134
mod_ocean_driver::ocean_driver_update
subroutine, public ocean_driver_update
Ocean step.
Definition: mod_ocean_driver.F90:994
mod_ocean_admin::ocean_ice_type
character(len=h_short), public ocean_ice_type
Definition: mod_ocean_admin.F90:40
scale_time::time_nowdaysec
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:72
mod_ocean_vars::ocean_sflx_mu
real(rp), dimension(:,:), allocatable, public ocean_sflx_mu
ocean surface u-momentum flux [kg/m/s2]
Definition: mod_ocean_vars.F90:113
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_cpl_sfc_index::i_r_direct
integer, parameter, public i_r_direct
Definition: scale_cpl_sfc_index.F90:37
mod_ocean_vars::atmos_pbl
real(rp), dimension(:,:), allocatable, public atmos_pbl
Definition: mod_ocean_vars.F90:95
mod_ocean_vars::ocean_ice_temp
real(rp), dimension(:,:), allocatable, public ocean_ice_temp
sea ice temperature [K]
Definition: mod_ocean_vars.F90:74
mod_ocean_vars::ocean_oflx_water
real(rp), dimension(:,:), pointer, public ocean_oflx_water
ocean-ice surface water mass flux [kg/m2/s]
Definition: mod_ocean_vars.F90:108
scale_ocean_grid_cartesc_real::ocean_grid_cartesc_real_totarea
real(rp), public ocean_grid_cartesc_real_totarea
total area
Definition: scale_ocean_grid_cartesC_real.F90:38
mod_ocean_vars::atmos_sflx_engi
real(rp), dimension(:,:), allocatable, public atmos_sflx_engi
Definition: mod_ocean_vars.F90:101
scale_tracer::qa
integer, public qa
Definition: scale_tracer.F90:35
scale_ocean_phy_ice_simple::ocean_phy_ice_adjustment
subroutine, public ocean_phy_ice_adjustment(OIA, OIS, OIE, OJA, OJS, OJE, calc_flag, OCEAN_DEPTH, OCEAN_TEMP, ICE_TEMP, ICE_MASS, MASS_FLUX, ENGI_FLUX, MASS_SUPL, ENGI_SUPL)
Definition: scale_ocean_phy_ice_simple.F90:205
scale_ocean_grid_cartesc_index::oke
integer, public oke
Definition: scale_ocean_grid_cartesC_index.F90:39
mod_ocean_vars::ocean_sfc_z0e
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0e
ocean surface roughness length for vapor [m]
Definition: mod_ocean_vars.F90:72
mod_ocean_admin::ocean_alb_type
character(len=h_short), public ocean_alb_type
Definition: mod_ocean_admin.F90:43
scale_ocean_phy_ice_simple
module ocean / physics / ice / simple
Definition: scale_ocean_phy_ice_simple.F90:12
mod_ocean_vars::ocean_sflx_mw
real(rp), dimension(:,:), allocatable, public ocean_sflx_mw
ocean surface w-momentum flux [kg/m/s2]
Definition: mod_ocean_vars.F90:112
mod_ocean_vars::ocean_salt_t
real(rp), dimension(:,:,:), allocatable, public ocean_salt_t
tendency of OCEAN_OCN_SALT
Definition: mod_ocean_vars.F90:80
scale_atmos_grid_cartesc_real::atmos_grid_cartesc_real_z1
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_z1
Height of the lowermost grid from surface (cell center) [m].
Definition: scale_atmos_grid_cartesC_real.F90:60
mod_ocean_driver::ocean_driver_finalize
subroutine, public ocean_driver_finalize
Finalize.
Definition: mod_ocean_driver.F90:190
scale_cpl_sfc_index::i_r_diffuse
integer, parameter, public i_r_diffuse
Definition: scale_cpl_sfc_index.F90:38
mod_ocean_vars::ocean_ice_rlmo
real(rp), dimension(:,:), allocatable, public ocean_ice_rlmo
Definition: mod_ocean_vars.F90:137
mod_cpl_vars
module COUPLER Variables
Definition: mod_cpl_vars.F90:12
mod_ocean_vars::ocean_q2
real(rp), dimension(:,:), allocatable, public ocean_q2
ocean surface water vapor at 2m [kg/kg]
Definition: mod_ocean_vars.F90:121
scale_ocean_grid_cartesc_index::oie
integer, public oie
Definition: scale_ocean_grid_cartesC_index.F90:44
scale_precision
module PRECISION
Definition: scale_precision.F90:14
mod_ocean_vars::ice_flag
logical, public ice_flag
Definition: mod_ocean_vars.F90:142
mod_atmos_admin
module ATMOS admin
Definition: mod_atmos_admin.F90:11
mod_ocean_driver::ocean_surface_get
subroutine, public ocean_surface_get
Get surface boundary from other model.
Definition: mod_ocean_driver.F90:1199
scale_ocean_phy_albedo_nakajima00::ocean_phy_albedo_nakajima00_setup
subroutine, public ocean_phy_albedo_nakajima00_setup
Definition: scale_ocean_phy_albedo_nakajima00.F90:49
scale_cpl_sfc_index::i_r_ir
integer, parameter, public i_r_ir
Definition: scale_cpl_sfc_index.F90:29
mod_ocean_vars::ocean_ustar
real(rp), dimension(:,:), allocatable, target, public ocean_ustar
ocean surface friction velocity [m/s]
Definition: mod_ocean_vars.F90:123
scale_const::const_eps
real(rp), public const_eps
small number
Definition: scale_const.F90:35
scale_ocean_phy_albedo::ocean_phy_albedo_const_setup
subroutine, public ocean_phy_albedo_const_setup
Definition: scale_ocean_phy_albedo.F90:63
scale_ocean_phy_roughness::ocean_phy_roughness_const
subroutine, public ocean_phy_roughness_const(OIA, OIS, OIE, OJA, OJS, OJE, Z0M, Z0H, Z0E)
Definition: scale_ocean_phy_roughness.F90:161
mod_ocean_vars::ocean_temp_t
real(rp), dimension(:,:,:), allocatable, public ocean_temp_t
tendency of OCEAN_OCN_TEMP
Definition: mod_ocean_vars.F90:79
scale_prof::prof_rapstart
subroutine, public prof_rapstart(rapname_base, level, disable_barrier)
Start raptime.
Definition: scale_prof.F90:174
scale_bulkflux
module Surface bulk flux
Definition: scale_bulkflux.F90:12
mod_ocean_vars::atmos_cossza
real(rp), dimension(:,:), allocatable, public atmos_cossza
Definition: mod_ocean_vars.F90:99
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
mod_ocean_vars::ocean_ice_wstar
real(rp), dimension(:,:), allocatable, public ocean_ice_wstar
Definition: mod_ocean_vars.F90:136
scale_ocean_grid_cartesc_index::oka
integer, public oka
Definition: scale_ocean_grid_cartesC_index.F90:37
scale_ocean_phy_roughness_moon07
module ocean / physics / surface roughness length / moon07
Definition: scale_ocean_phy_roughness_moon07.F90:15
mod_ocean_vars::ocean_ice_qstar
real(rp), dimension(:,:), allocatable, public ocean_ice_qstar
Definition: mod_ocean_vars.F90:135
scale_ocean_grid_cartesc_index::okmax
integer, public okmax
Definition: scale_ocean_grid_cartesC_index.F90:32
mod_atmos_phy_ch_driver::atmos_phy_ch_driver_ocean_flux
subroutine, public atmos_phy_ch_driver_ocean_flux(SFLX_QTRC)
Driver.
Definition: mod_atmos_phy_ch_driver.F90:261
mod_ocean_vars::ocean_v10
real(rp), dimension(:,:), allocatable, public ocean_v10
ocean surface velocity v at 10m [m/s]
Definition: mod_ocean_vars.F90:119
mod_ocean_vars::ocean_sfc_z0m
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0m
ocean surface roughness length for momentum [m]
Definition: mod_ocean_vars.F90:70
scale_atmos_hydrometeor::atmos_hydrometeor_dry
logical, public atmos_hydrometeor_dry
Definition: scale_atmos_hydrometeor.F90:114
scale_cpl_phy_sfc_fixed_temp::cpl_phy_sfc_fixed_temp_setup
subroutine, public cpl_phy_sfc_fixed_temp_setup
Setup.
Definition: scale_cpl_phy_sfc_fixed_temp.F90:51
scale_ocean_phy_albedo_nakajima00
module ocean / physics / surface albedo / nakajima00
Definition: scale_ocean_phy_albedo_nakajima00.F90:15
scale_ocean_phy_tc::ocean_phy_tc_seaice_setup
subroutine, public ocean_phy_tc_seaice_setup
Definition: scale_ocean_phy_tc.F90:49
mod_ocean_vars::ocean_sflx_qtrc
real(rp), dimension(:,:,:), allocatable, public ocean_sflx_qtrc
ocean surface tracer flux [kg/m2/s]
Definition: mod_ocean_vars.F90:117
scale_ocean_grid_cartesc
module ocean / grid / cartesianC
Definition: scale_ocean_grid_cartesC.F90:12
scale_ocean_grid_cartesc_real::ocean_grid_cartesc_real_area
real(rp), dimension(:,:), allocatable, public ocean_grid_cartesc_real_area
area of grid cell
Definition: scale_ocean_grid_cartesC_real.F90:37
scale_atmos_grid_cartesc_real
module Atmosphere GRID CartesC Real(real space)
Definition: scale_atmos_grid_cartesC_real.F90:11
scale_file_history
module file_history
Definition: scale_file_history.F90:15
scale_ocean_grid_cartesc_index::ois
integer, public ois
Definition: scale_ocean_grid_cartesC_index.F90:43
mod_ocean_vars::ocean_sflx_sh
real(rp), dimension(:,:), allocatable, public ocean_sflx_sh
ocean surface sensible heat flux [J/m2/s]
Definition: mod_ocean_vars.F90:115
mod_ocean_vars::ocean_ocn_tstar
real(rp), dimension(:,:), pointer, public ocean_ocn_tstar
Definition: mod_ocean_vars.F90:129
mod_ocean_vars::ocean_ocn_ustar
real(rp), dimension(:,:), pointer, public ocean_ocn_ustar
Definition: mod_ocean_vars.F90:128
scale_ocean_dyn_slab::ocean_dyn_slab_setup
subroutine, public ocean_dyn_slab_setup(DEPTH)
Setup.
Definition: scale_ocean_dyn_slab.F90:54
mod_ocean_driver::ocean_surface_set
subroutine, public ocean_surface_set(countup)
Put surface boundary to other model.
Definition: mod_ocean_driver.F90:1248
scale_ocean_phy_roughness_moon07::ocean_phy_roughness_moon07_setup
subroutine, public ocean_phy_roughness_moon07_setup
Definition: scale_ocean_phy_roughness_moon07.F90:51
mod_ocean_vars::ocean_oflx_gh
real(rp), dimension(:,:), pointer, public ocean_oflx_gh
ocean-ice surface water heat flux [J/m2/s]
Definition: mod_ocean_vars.F90:107
scale_prc
module PROCESS
Definition: scale_prc.F90:11
mod_ocean_vars::ocean_sflx_gh
real(rp), dimension(:,:), allocatable, target, public ocean_sflx_gh
ocean surface water heat flux [J/m2/s]
Definition: mod_ocean_vars.F90:104
mod_ocean_admin::ocean_sfc_type
character(len=h_short), public ocean_sfc_type
Definition: mod_ocean_admin.F90:39
scale_ocean_grid_cartesc_index::oje
integer, public oje
Definition: scale_ocean_grid_cartesC_index.F90:49
mod_ocean_vars::ocean_vvel_t
real(rp), dimension(:,:,:), allocatable, public ocean_vvel_t
tendency of OCEAN_OCN_VVEL
Definition: mod_ocean_vars.F90:82
mod_ocean_vars::ocean_ocn_qstar
real(rp), dimension(:,:), pointer, public ocean_ocn_qstar
Definition: mod_ocean_vars.F90:130
scale_io
module STDIO
Definition: scale_io.F90:10
scale_ocean_phy_roughness_miller92::ocean_phy_roughness_miller92_setup
subroutine, public ocean_phy_roughness_miller92_setup
Definition: scale_ocean_phy_roughness_miller92.F90:57
scale_ocean_phy_roughness_miller92::ocean_phy_roughness_miller92
subroutine, public ocean_phy_roughness_miller92(OIA, OIS, OIE, OJA, OJS, OJE, Uabs, Z0M, Z0H, Z0E)
Definition: scale_ocean_phy_roughness_miller92.F90:101
mod_ocean_vars::ocean_engi_supl
real(rp), dimension(:,:), allocatable, public ocean_engi_supl
Definition: mod_ocean_vars.F90:146
mod_ocean_vars::atmos_sflx_water
real(rp), dimension(:,:), allocatable, public atmos_sflx_water
Definition: mod_ocean_vars.F90:100
mod_ocean_vars::ocean_sfc_z0h
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0h
ocean surface roughness length for heat [m]
Definition: mod_ocean_vars.F90:71
mod_ocean_admin
module Ocean admin
Definition: mod_ocean_admin.F90:11
scale_ocean_grid_cartesc_index::oja
integer, public oja
Definition: scale_ocean_grid_cartesC_index.F90:47
mod_ocean_vars::ocean_uvel_t
real(rp), dimension(:,:,:), allocatable, public ocean_uvel_t
tendency of OCEAN_OCN_UVEL
Definition: mod_ocean_vars.F90:81
scale_tracer::k
real(rp), public k
Definition: scale_tracer.F90:45
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_ocean_phy_albedo_nakajima00::ocean_phy_albedo_nakajima00
subroutine, public ocean_phy_albedo_nakajima00(OIA, OIS, OIE, OJA, OJS, OJE, cosSZA, SFC_albedo)
Definition: scale_ocean_phy_albedo_nakajima00.F90:63
mod_ocean_vars::ocean_uvel
real(rp), dimension(:,:,:), allocatable, public ocean_uvel
ocean zonal velocity [m/s]
Definition: mod_ocean_vars.F90:63
mod_ocean_admin::ocean_dyn_type
character(len=h_short), public ocean_dyn_type
Definition: mod_ocean_admin.F90:34
scale_ocean_phy_albedo::ocean_phy_albedo_seaice_setup
subroutine, public ocean_phy_albedo_seaice_setup
Definition: scale_ocean_phy_albedo.F90:97
mod_ocean_vars::atmos_sflx_rad_dn
real(rp), dimension(:,:,:,:), allocatable, public atmos_sflx_rad_dn
Definition: mod_ocean_vars.F90:98
scale_ocean_phy_tc
module ocean / physics / surface thermal conductivity
Definition: scale_ocean_phy_tc.F90:12
mod_cpl_vars::cpl_putocn
subroutine, public cpl_putocn(SFC_TEMP, SFC_albedo, SFC_Z0M, SFC_Z0H, SFC_Z0E, SFLX_MW, SFLX_MU, SFLX_MV, SFLX_SH, SFLX_LH, SFLX_GH, SFLX_QTRC, U10, V10, T2, Q2, mask, countup)
Definition: mod_cpl_vars.F90:793
mod_ocean_vars::atmos_sfc_dens
real(rp), dimension(:,:), allocatable, public atmos_sfc_dens
Definition: mod_ocean_vars.F90:96
mod_ocean_vars::ocean_ice_temp_t
real(rp), dimension(:,:), allocatable, public ocean_ice_temp_t
tendency of OCEAN_ICE_TEMP
Definition: mod_ocean_vars.F90:84
scale_const::const_huge
real(rp), public const_huge
huge number
Definition: scale_const.F90:37
mod_ocean_admin::ocean_rgn_type
character(len=h_short), public ocean_rgn_type
Definition: mod_ocean_admin.F90:45
scale_ocean_phy_albedo
module ocean / physics / surface albedo
Definition: scale_ocean_phy_albedo.F90:12
mod_ocean_driver::ocean_driver_calc_tendency
subroutine, public ocean_driver_calc_tendency(force)
Calculate tendency.
Definition: mod_ocean_driver.F90:245
scale_ocean_grid_cartesc::ocean_grid_cartesc_cdz
real(rp), dimension(:), allocatable, public ocean_grid_cartesc_cdz
z-length of control volume [m]
Definition: scale_ocean_grid_cartesC.F90:38
scale_prof
module profiler
Definition: scale_prof.F90:11
mod_ocean_vars::ocean_tstar
real(rp), dimension(:,:), allocatable, target, public ocean_tstar
ocean surface tempreture scale [K]
Definition: mod_ocean_vars.F90:124
scale_time::time_dtsec_ocean
real(dp), public time_dtsec_ocean
time interval of ocean step [sec]
Definition: scale_time.F90:46
mod_ocean_vars::atmos_temp
real(rp), dimension(:,:), allocatable, public atmos_temp
Definition: mod_ocean_vars.F90:88
mod_ocean_vars
module OCEAN Variables
Definition: mod_ocean_vars.F90:12
scale_ocean_grid_cartesc_index
module ocean / grid / cartesianC / index
Definition: scale_ocean_grid_cartesC_index.F90:11
mod_atmos_admin::atmos_sw_phy_ch
logical, public atmos_sw_phy_ch
Definition: mod_atmos_admin.F90:54
scale_ocean_phy_tc::ocean_phy_tc_seaice
subroutine, public ocean_phy_tc_seaice(OIA, OIS, OIE, OJA, OJS, OJE, ICE_MASS, ICE_FRAC, mask, TC_dz)
Definition: scale_ocean_phy_tc.F90:85
scale_time
module TIME
Definition: scale_time.F90:11
mod_ocean_vars::ocean_ocn_rlmo
real(rp), dimension(:,:), pointer, public ocean_ocn_rlmo
Definition: mod_ocean_vars.F90:132
scale_ocean_phy_albedo::ocean_phy_albedo_seaice
subroutine, public ocean_phy_albedo_seaice(OIA, OIS, OIE, OJA, OJS, OJE, SFC_albedo)
Definition: scale_ocean_phy_albedo.F90:166
mod_ocean_vars::ocean_wstar
real(rp), dimension(:,:), allocatable, target, public ocean_wstar
ocean surface convective velocity scale [m/s]
Definition: mod_ocean_vars.F90:126
scale_ocean_phy_roughness
module ocean / physics / surface roughness length
Definition: scale_ocean_phy_roughness.F90:12
scale_tracer
module TRACER
Definition: scale_tracer.F90:12
scale_atmos_hydrometeor::i_qv
integer, public i_qv
Definition: scale_atmos_hydrometeor.F90:93
mod_ocean_vars::ocean_mass_supl
real(rp), dimension(:,:), allocatable, public ocean_mass_supl
Definition: mod_ocean_vars.F90:145
mod_ocean_vars::ocean_oflx_engi
real(rp), dimension(:,:), pointer, public ocean_oflx_engi
ocean-ice surface internal energy flux [J/m2/s]
Definition: mod_ocean_vars.F90:109
mod_ocean_vars::ocean_sflx_water
real(rp), dimension(:,:), allocatable, target, public ocean_sflx_water
ocean surface water mass flux [kg/m2/s]
Definition: mod_ocean_vars.F90:105
scale_ocean_phy_ice_simple::ocean_phy_ice_simple
subroutine, public ocean_phy_ice_simple(OIA, OIS, OIE, OJA, OJS, OJE, iflx_water, iflx_hbalance, subsfc_temp, TC_dz, ICE_TEMP, ICE_MASS, ICE_FRAC, calc_flag, dt, ICE_TEMP_t, ICE_MASS_t, sflx_G, sflx_water, sflx_RHOE)
Slab ocean model.
Definition: scale_ocean_phy_ice_simple.F90:309
scale_ocean_dyn_offline::ocean_dyn_offline
subroutine, public ocean_dyn_offline(OKMAX, OKS, OKE, OIA, OIS, OIE, OJA, OJS, OJE, calc_flag, dt, NOWDAYSEC, OCEAN_TEMP)
Slab ocean model.
Definition: scale_ocean_dyn_offline.F90:130
mod_ocean_vars::ocean_ice_tstar
real(rp), dimension(:,:), allocatable, public ocean_ice_tstar
Definition: mod_ocean_vars.F90:134
scale_landuse::landuse_exists_ocean
logical, dimension(:,:), allocatable, public landuse_exists_ocean
ocean calculation flag
Definition: scale_landuse.F90:50
mod_atmos_phy_ch_driver
module ATMOSPHERE / Physics Chemistry
Definition: mod_atmos_phy_ch_driver.F90:12
mod_ocean_admin::ocean_do
logical, public ocean_do
Definition: mod_ocean_admin.F90:32
mod_ocean_vars::ocean_ice_mass
real(rp), dimension(:,:), allocatable, public ocean_ice_mass
sea ice mass [kg]
Definition: mod_ocean_vars.F90:75
scale_ocean_grid_cartesc_real::ocean_grid_cartesc_real_vol
real(rp), dimension(:,:,:), allocatable, public ocean_grid_cartesc_real_vol
volume of grid cell
Definition: scale_ocean_grid_cartesC_real.F90:39
mod_ocean_vars::ocean_vvel
real(rp), dimension(:,:,:), allocatable, public ocean_vvel
ocean meridional velocity [m/s]
Definition: mod_ocean_vars.F90:64
scale_statistics::statistics_checktotal
logical, public statistics_checktotal
calc&report variable totals to logfile?
Definition: scale_statistics.F90:109
scale_cpl_sfc_index
module coupler / surface-atmospehre
Definition: scale_cpl_sfc_index.F90:11
mod_ocean_driver::ocean_driver_setup
subroutine, public ocean_driver_setup
Setup.
Definition: mod_ocean_driver.F90:58
mod_ocean_vars::ocean_sflx_engi
real(rp), dimension(:,:), allocatable, target, public ocean_sflx_engi
ocean surface internal energy flux [J/m2/s]
Definition: mod_ocean_vars.F90:106
scale_ocean_grid_cartesc_index::ojs
integer, public ojs
Definition: scale_ocean_grid_cartesC_index.F90:48
scale_cpl_sfc_index::i_r_vis
integer, parameter, public i_r_vis
Definition: scale_cpl_sfc_index.F90:31
scale_ocean_phy_ice_simple::ocean_phy_ice_setup
subroutine, public ocean_phy_ice_setup
Definition: scale_ocean_phy_ice_simple.F90:60
mod_ocean_vars::atmos_v
real(rp), dimension(:,:), allocatable, public atmos_v
Definition: mod_ocean_vars.F90:92
mod_cpl_vars::cpl_getatm_ocn
subroutine, public cpl_getatm_ocn(TEMP, PRES, W, U, V, DENS, QV, PBL, SFC_DENS, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_water, SFLX_ENGI)
Definition: mod_cpl_vars.F90:1308
mod_ocean_vars::ocean_sfc_albedo
real(rp), dimension(:,:,:,:), allocatable, public ocean_sfc_albedo
ocean surface albedo (direct/diffuse,IR/near-IR/VIS) (0-1)
Definition: mod_ocean_vars.F90:69
mod_ocean_vars::atmos_dens
real(rp), dimension(:,:), allocatable, public atmos_dens
Definition: mod_ocean_vars.F90:93
scale_ocean_phy_roughness::ocean_phy_roughness_seaice_setup
subroutine, public ocean_phy_roughness_seaice_setup
Definition: scale_ocean_phy_roughness.F90:127
scale_cpl_phy_sfc_fixed_temp::cpl_phy_sfc_fixed_temp
subroutine, public cpl_phy_sfc_fixed_temp(IA, IS, IE, JA, JS, JE, TMPA, PRSA, WA, UA, VA, RHOA, QVA, LH, Z1, PBL, RHOS, PRSS, RFLXD, TMPS, WSTR, QVEF, ALBEDO, Rb, Z0M, Z0H, Z0E, calc_flag, dt, ZMFLX, XMFLX, YMFLX, SHFLX, LHFLX, QVFLX, GFLX, Ustar, Tstar, Qstar, Wstar, RLmo, U10, V10, T2, Q2)
Definition: scale_cpl_phy_sfc_fixed_temp.F90:94
mod_ocean_vars::ocean_sfc_temp
real(rp), dimension(:,:), allocatable, public ocean_sfc_temp
ocean surface skin temperature [K]
Definition: mod_ocean_vars.F90:68
scale_atmos_hydrometeor::lhf
real(rp), public lhf
latent heat of fusion for use [J/kg]
Definition: scale_atmos_hydrometeor.F90:146
scale_ocean_phy_roughness::ocean_phy_roughness_const_setup
subroutine, public ocean_phy_roughness_const_setup
Definition: scale_ocean_phy_roughness.F90:96
scale_ocean_phy_ice_simple::ocean_phy_ice_fraction
subroutine, public ocean_phy_ice_fraction(OIA, OIS, OIE, OJA, OJS, OJE, ICE_MASS, ICE_FRAC)
Definition: scale_ocean_phy_ice_simple.F90:167
scale_prof::prof_rapend
subroutine, public prof_rapend(rapname_base, level, disable_barrier)
Save raptime.
Definition: scale_prof.F90:246
scale_ocean_grid_cartesc_real
module ocean / grid / cartesianC / real
Definition: scale_ocean_grid_cartesC_real.F90:12
mod_ocean_vars::ocean_rlmo
real(rp), dimension(:,:), allocatable, target, public ocean_rlmo
ocean surface inversed Obukhov length [1/m]
Definition: mod_ocean_vars.F90:127
scale_ocean_grid_cartesc_index::oia
integer, public oia
Definition: scale_ocean_grid_cartesC_index.F90:42
mod_ocean_vars::ocean_ice_frac
real(rp), dimension(:,:), allocatable, public ocean_ice_frac
area fraction of sea ice [1]
Definition: mod_ocean_vars.F90:140
mod_ocean_vars::ocean_sflx_lh
real(rp), dimension(:,:), allocatable, public ocean_sflx_lh
ocean surface latent heat flux [J/m2/s]
Definition: mod_ocean_vars.F90:116
mod_ocean_vars::ocean_salt
real(rp), dimension(:,:,:), allocatable, public ocean_salt
ocean salinity [PSU]
Definition: mod_ocean_vars.F90:62
scale_landuse
module LANDUSE
Definition: scale_landuse.F90:19
mod_ocean_vars::ocean_ice_mass_t
real(rp), dimension(:,:), allocatable, public ocean_ice_mass_t
tendency of OCEAN_ICE_MASS
Definition: mod_ocean_vars.F90:85
mod_ocean_vars::atmos_pres
real(rp), dimension(:,:), allocatable, public atmos_pres
Definition: mod_ocean_vars.F90:89
scale_cpl_sfc_index::n_rad_rgn
integer, parameter, public n_rad_rgn
Definition: scale_cpl_sfc_index.F90:28
mod_ocean_vars::ocean_u10
real(rp), dimension(:,:), allocatable, public ocean_u10
ocean surface velocity u at 10m [m/s]
Definition: mod_ocean_vars.F90:118
mod_ocean_vars::atmos_u
real(rp), dimension(:,:), allocatable, public atmos_u
Definition: mod_ocean_vars.F90:91
mod_ocean_vars::ocean_ocn_wstar
real(rp), dimension(:,:), pointer, public ocean_ocn_wstar
Definition: mod_ocean_vars.F90:131
scale_ocean_phy_roughness_miller92
module ocean / physics / surface roughness length / miller92
Definition: scale_ocean_phy_roughness_miller92.F90:12
mod_ocean_vars::ocean_qstar
real(rp), dimension(:,:), allocatable, target, public ocean_qstar
ocean surface moisture scale [kg/kg]
Definition: mod_ocean_vars.F90:125
scale_atmos_hydrometeor::cv_water
real(rp), public cv_water
CV for water [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:151
mod_ocean_vars::ocean_t2
real(rp), dimension(:,:), allocatable, public ocean_t2
ocean surface temperature at 2m [K]
Definition: mod_ocean_vars.F90:120
scale_ocean_grid_cartesc_real::ocean_grid_cartesc_real_totvol
real(rp), public ocean_grid_cartesc_real_totvol
total volume
Definition: scale_ocean_grid_cartesC_real.F90:40
scale_atmos_hydrometeor::cv_ice
real(rp), public cv_ice
CV for ice [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:153
scale_ocean_phy_roughness_moon07::ocean_phy_roughness_moon07
subroutine, public ocean_phy_roughness_moon07(OIA, OIS, OIE, OJA, OJS, OJE, Uabs, Z1, mask, Z0M, Z0H, Z0E)
Definition: scale_ocean_phy_roughness_moon07.F90:86
mod_ocean_vars::atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
Definition: mod_ocean_vars.F90:97
scale_ocean_dyn_slab
module ocean / dynamics / slab
Definition: scale_ocean_dyn_slab.F90:12
mod_ocean_vars::ocean_vars_check
subroutine, public ocean_vars_check(force)
Budget monitor for ocean.
Definition: mod_ocean_vars.F90:999
scale_cpl_phy_sfc_fixed_temp
module coupler / surface fixed temp model
Definition: scale_cpl_phy_sfc_fixed_temp.F90:12
mod_ocean_vars::ocean_temp
real(rp), dimension(:,:,:), allocatable, public ocean_temp
ocean temperature [K]
Definition: mod_ocean_vars.F90:61
mod_ocean_vars::ocean_ice_ustar
real(rp), dimension(:,:), allocatable, public ocean_ice_ustar
Definition: mod_ocean_vars.F90:133
mod_ocean_vars::atmos_qv
real(rp), dimension(:,:), allocatable, public atmos_qv
Definition: mod_ocean_vars.F90:94
scale_ocean_grid_cartesc_index::oks
integer, public oks
Definition: scale_ocean_grid_cartesC_index.F90:38