SCALE-RM
Functions/Subroutines
mod_ocean_phy_driver Module Reference

module OCEAN / Physics More...

Functions/Subroutines

subroutine, public ocean_phy_driver_setup
 Setup. More...
 
subroutine, public ocean_phy_driver_resume
 Resume. More...
 
subroutine, public ocean_phy_driver (update_flag)
 Driver. More...
 

Detailed Description

module OCEAN / Physics

Description
ocean physics module
Author
Team SCALE
NAMELIST
  • No namelist group
History Output
namedescriptionunitvariable
OCEAN_ALB_LW_t tendency of OCEAN_ALB_LW 0-1 OCEAN_SFC_albedo_t
OCEAN_ALB_SW_t tendency of OCEAN_ALB_SW 0-1 OCEAN_SFC_albedo_t
OCEAN_SFC_TEMP_t tendency of OCEAN_SFC_TEMP K OCEAN_SFC_TEMP_t
OCEAN_SFC_Z0E_t tendency of OCEAN_SFC_Z0E m OCEAN_SFC_Z0E_t
OCEAN_SFC_Z0H_t tendency of OCEAN_SFC_Z0H m OCEAN_SFC_Z0H_t
OCEAN_SFC_Z0M_t tendency of OCEAN_SFC_Z0M m OCEAN_SFC_Z0M_t
OCEAN_TEMP_t tendency of OCEAN_TEMP K OCEAN_TEMP_t

Function/Subroutine Documentation

◆ ocean_phy_driver_setup()

subroutine, public mod_ocean_phy_driver::ocean_phy_driver_setup ( )

Setup.

Definition at line 53 of file mod_ocean_phy_driver.f90.

References scale_stdio::io_fid_log, scale_stdio::io_l, scale_ocean_phy::ocean_phy_setup(), scale_ocean_sfc::ocean_sfc_setup(), mod_ocean_admin::ocean_sw, and mod_ocean_admin::ocean_type.

Referenced by mod_ocean_driver::ocean_driver_setup().

53  use scale_ocean_phy, only: &
55  use scale_ocean_sfc, only: &
57  use mod_ocean_admin, only: &
58  ocean_type, &
59  ocean_sw
60  implicit none
61  !---------------------------------------------------------------------------
62 
63  if( io_l ) write(io_fid_log,*)
64  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[OCEAN PHY] / Origin[SCALE-RM]'
65 
66  if ( ocean_sw ) then
67 
68  ! setup library component
71 
72  else
73  if( io_l ) write(io_fid_log,*) '*** this component is never called.'
74  endif
75 
76  return
logical, public ocean_sw
subroutine, public ocean_sfc_setup(OCEAN_TYPE)
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
subroutine, public ocean_phy_setup(OCEAN_TYPE)
Setup.
module Ocean admin
module OCEAN / Physics
module OCEAN / Surface fluxes
character(len=h_short), public ocean_type
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ocean_phy_driver_resume()

subroutine, public mod_ocean_phy_driver::ocean_phy_driver_resume ( )

Resume.

Definition at line 82 of file mod_ocean_phy_driver.f90.

References ocean_phy_driver(), mod_ocean_admin::ocean_sw, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), and mod_admin_restart::restart_run.

Referenced by mod_ocean_driver::ocean_driver_resume().

82  use mod_admin_restart, only: &
84  use mod_ocean_admin, only: &
85  ocean_sw
86  implicit none
87 
88  if ( ocean_sw ) then
89 
90  if ( .NOT. restart_run ) then ! tentative
91  ! run once (only for the diagnostic value)
92  call prof_rapstart('OCN_Physics', 1)
93  call ocean_phy_driver( update_flag = .true. )
94  call prof_rapend ('OCN_Physics', 1)
95  end if
96 
97  end if
98 
99  return
logical, public ocean_sw
module Ocean admin
module administrator for restart
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
subroutine, public ocean_phy_driver(update_flag)
Driver.
logical, public restart_run
is this run restart?
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
Here is the call graph for this function:
Here is the caller graph for this function:

◆ ocean_phy_driver()

subroutine, public mod_ocean_phy_driver::ocean_phy_driver ( logical, intent(in)  update_flag)

Driver.

Definition at line 105 of file mod_ocean_phy_driver.f90.

References mod_ocean_vars::atmos_cossza, mod_ocean_vars::atmos_dens, mod_ocean_vars::atmos_pbl, mod_ocean_vars::atmos_pres, mod_ocean_vars::atmos_qv, mod_ocean_vars::atmos_sfc_pres, mod_ocean_vars::atmos_sflx_lw, mod_ocean_vars::atmos_sflx_prec, mod_ocean_vars::atmos_sflx_sw, mod_ocean_vars::atmos_temp, mod_ocean_vars::atmos_u, mod_ocean_vars::atmos_v, mod_ocean_vars::atmos_w, scale_grid_index::ie, scale_grid_index::is, scale_grid_index::je, scale_grid_index::js, scale_ocean_phy::ocean_phy, mod_ocean_vars::ocean_q2, scale_ocean_sfc::ocean_sfc, mod_ocean_vars::ocean_sfc_albedo, mod_ocean_vars::ocean_sfc_albedo_t, scale_ocean_sfc::ocean_sfc_simplealbedo, mod_ocean_vars::ocean_sfc_temp, mod_ocean_vars::ocean_sfc_temp_t, mod_ocean_vars::ocean_sfc_z0e, mod_ocean_vars::ocean_sfc_z0e_t, mod_ocean_vars::ocean_sfc_z0h, mod_ocean_vars::ocean_sfc_z0h_t, mod_ocean_vars::ocean_sfc_z0m, mod_ocean_vars::ocean_sfc_z0m_t, mod_ocean_vars::ocean_sflx_evap, mod_ocean_vars::ocean_sflx_lh, mod_ocean_vars::ocean_sflx_mu, mod_ocean_vars::ocean_sflx_mv, mod_ocean_vars::ocean_sflx_mw, mod_ocean_vars::ocean_sflx_sh, mod_ocean_vars::ocean_sflx_wh, mod_ocean_vars::ocean_t2, mod_ocean_vars::ocean_temp, mod_ocean_vars::ocean_temp_t, mod_ocean_vars::ocean_u10, mod_ocean_vars::ocean_v10, scale_grid_real::real_z1, scale_roughness::roughness, scale_rm_statistics::statistics_checktotal, and scale_time::time_dtsec_ocean.

Referenced by mod_ocean_driver::ocean_driver(), and ocean_phy_driver_resume().

105  use scale_atmos_thermodyn, only: &
106  atmos_thermodyn_templhv
107  use scale_time, only: &
108  dt => time_dtsec_ocean
109  use scale_rm_statistics, only: &
111  stat_total
112  use scale_history, only: &
113  hist_in
114  use scale_grid_real, only: &
115  real_z1
116  use scale_roughness, only: &
117  roughness
118  use scale_ocean_phy, only: &
119  ocean_phy
120  use scale_ocean_sfc, only: &
121  ocean_sfc, &
123  use mod_ocean_vars, only: &
124  ocean_temp, &
125  ocean_sfc_temp, &
127  ocean_sfc_z0m, &
128  ocean_sfc_z0h, &
129  ocean_sfc_z0e, &
130  ocean_temp_t, &
133  ocean_sfc_z0m_t, &
134  ocean_sfc_z0h_t, &
135  ocean_sfc_z0e_t, &
136  ocean_sflx_mw, &
137  ocean_sflx_mu, &
138  ocean_sflx_mv, &
139  ocean_sflx_sh, &
140  ocean_sflx_lh, &
141  ocean_sflx_wh, &
142  ocean_sflx_evap, &
143  ocean_u10, &
144  ocean_v10, &
145  ocean_t2, &
146  ocean_q2, &
147  atmos_temp, &
148  atmos_pres, &
149  atmos_w, &
150  atmos_u, &
151  atmos_v, &
152  atmos_dens, &
153  atmos_qv, &
154  atmos_pbl, &
155  atmos_sfc_pres, &
156  atmos_sflx_lw, &
157  atmos_sflx_sw, &
158  atmos_cossza, &
160  implicit none
161 
162  logical, intent(in) :: update_flag
163 
164  real(RP) :: total ! dummy
165  real(RP) :: lhv(ia,ja)
166 
167  integer :: i, j
168  !---------------------------------------------------------------------------
169 
170  if ( update_flag ) then
171 
172  call roughness( ocean_sfc_z0m_t(:,:), & ! [OUT]
173  ocean_sfc_z0h_t(:,:), & ! [OUT]
174  ocean_sfc_z0e_t(:,:), & ! [OUT]
175  ocean_sfc_z0m(:,:), & ! [IN]
176  ocean_sfc_z0h(:,:), & ! [IN]
177  ocean_sfc_z0e(:,:), & ! [IN]
178  atmos_u(:,:), & ! [IN]
179  atmos_v(:,:), & ! [IN]
180  real_z1(:,:), & ! [IN]
181  dt ) ! [IN]
182 
183  call ocean_sfc_simplealbedo( ocean_sfc_albedo_t(:,:,:), & ! [OUT]
184  ocean_sfc_albedo(:,:,:), & ! [IN]
185  atmos_cossza(:,:), & ! [IN]
186  dt ) ! [IN]
187 
188  call ocean_sfc( ocean_sfc_temp_t(:,:), & ! [OUT]
189  ocean_sflx_mw(:,:), & ! [OUT]
190  ocean_sflx_mu(:,:), & ! [OUT]
191  ocean_sflx_mv(:,:), & ! [OUT]
192  ocean_sflx_sh(:,:), & ! [OUT]
193  ocean_sflx_lh(:,:), & ! [OUT]
194  ocean_sflx_wh(:,:), & ! [OUT]
195  ocean_u10(:,:), & ! [OUT]
196  ocean_v10(:,:), & ! [OUT]
197  ocean_t2(:,:), & ! [OUT]
198  ocean_q2(:,:), & ! [OUT]
199  atmos_temp(:,:), & ! [IN]
200  atmos_pres(:,:), & ! [IN]
201  atmos_w(:,:), & ! [IN]
202  atmos_u(:,:), & ! [IN]
203  atmos_v(:,:), & ! [IN]
204  atmos_dens(:,:), & ! [IN]
205  atmos_qv(:,:), & ! [IN]
206  real_z1(:,:), & ! [IN]
207  atmos_pbl(:,:), & ! [IN]
208  atmos_sfc_pres(:,:), & ! [IN]
209  atmos_sflx_lw(:,:), & ! [IN]
210  atmos_sflx_sw(:,:), & ! [IN]
211  ocean_temp(:,:), & ! [IN]
212  ocean_sfc_temp(:,:), & ! [IN]
213  ocean_sfc_albedo(:,:,i_lw), & ! [IN]
214  ocean_sfc_albedo(:,:,i_sw), & ! [IN]
215  ocean_sfc_z0m(:,:), & ! [IN]
216  ocean_sfc_z0h(:,:), & ! [IN]
217  ocean_sfc_z0e(:,:), & ! [IN]
218  dt ) ! [IN]
219 
220 
221  call atmos_thermodyn_templhv( lhv, atmos_temp )
222 
223 !OCL XFILL
224  do j = js, je
225  do i = is, ie
226  ocean_sflx_evap(i,j) = ocean_sflx_lh(i,j) / lhv(i,j)
227  end do
228  end do
229 
230  call ocean_phy( ocean_temp_t(:,:), & ! [OUT]
231  ocean_temp(:,:), & ! [IN]
232  ocean_sflx_wh(:,:), & ! [IN]
233  atmos_sflx_prec(:,:), & ! [IN]
234  ocean_sflx_evap(:,:), & ! [IN]
235  dt ) ! [IN]
236 
237  call hist_in( ocean_temp_t(:,:), 'OCEAN_TEMP_t', 'tendency of OCEAN_TEMP', 'K' )
238  call hist_in( ocean_sfc_temp_t(:,:), 'OCEAN_SFC_TEMP_t', 'tendency of OCEAN_SFC_TEMP', 'K' )
239  call hist_in( ocean_sfc_albedo_t(:,:,i_lw), 'OCEAN_ALB_LW_t', 'tendency of OCEAN_ALB_LW', '0-1' )
240  call hist_in( ocean_sfc_albedo_t(:,:,i_sw), 'OCEAN_ALB_SW_t', 'tendency of OCEAN_ALB_SW', '0-1' )
241  call hist_in( ocean_sfc_z0m_t(:,:), 'OCEAN_SFC_Z0M_t', 'tendency of OCEAN_SFC_Z0M', 'm' )
242  call hist_in( ocean_sfc_z0h_t(:,:), 'OCEAN_SFC_Z0H_t', 'tendency of OCEAN_SFC_Z0H', 'm' )
243  call hist_in( ocean_sfc_z0e_t(:,:), 'OCEAN_SFC_Z0E_t', 'tendency of OCEAN_SFC_Z0E', 'm' )
244 
245  end if
246 
247  if ( statistics_checktotal ) then
248  call stat_total( total, ocean_temp_t(:,:), 'OCEAN_TEMP_t' )
249  call stat_total( total, ocean_sfc_temp_t(:,:), 'OCEAN_SFC_TEMP_t' )
250  call stat_total( total, ocean_sfc_albedo_t(:,:,i_lw), 'OCEAN_ALB_LW_t' )
251  call stat_total( total, ocean_sfc_albedo_t(:,:,i_sw), 'OCEAN_ALB_SW_t' )
252  call stat_total( total, ocean_sfc_z0m_t(:,:), 'OCEAN_SFC_Z0M_t' )
253  call stat_total( total, ocean_sfc_z0h_t(:,:), 'OCEAN_SFC_Z0H_t' )
254  call stat_total( total, ocean_sfc_z0e_t(:,:), 'OCEAN_SFC_Z0E_t' )
255  end if
256 
257  return
real(rp), dimension(:,:), allocatable, public ocean_v10
ocean surface velocity v at 10m [m/s]
real(dp), public time_dtsec_ocean
time interval of ocean step [sec]
Definition: scale_time.F90:47
integer, public is
start point of inner domain: x, local
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
procedure(alb), pointer, public ocean_sfc_simplealbedo
real(rp), dimension(:,:,:), allocatable, public ocean_sfc_albedo
ocean surface albedo [0-1]
real(rp), dimension(:,:), allocatable, public atmos_dens
real(rp), dimension(:,:,:), allocatable, public ocean_sfc_albedo_t
tendency of OCEAN_SFC_alebdo
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]
real(rp), dimension(:,:), allocatable, public atmos_v
procedure(ocnsfc), pointer, public ocean_sfc
real(rp), dimension(:,:), allocatable, public ocean_sflx_wh
ocean surface water heat flux [J/m2/s]
real(rp), dimension(:,:), allocatable, public atmos_sflx_lw
real(rp), dimension(:,:), allocatable, public ocean_temp_t
tendency of OCEAN_TEMP
integer, parameter, public i_lw
module Statistics
integer, parameter, public i_sw
real(rp), dimension(:,:), allocatable, public atmos_cossza
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]
real(rp), dimension(:,:), allocatable, public real_z1
Height of the lowermost grid from surface (cell center) [m].
module GRID (real space)
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_qv
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0h_t
tendency of OCEAN_SFC_Z0H
integer, public js
start point of inner domain: y, local
procedure(rl), pointer, public roughness
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
module OCEAN / Physics
real(rp), dimension(:,:), allocatable, public atmos_temp
real(rp), dimension(:,:), allocatable, public ocean_sflx_mw
ocean surface w-momentum flux [kg/m2/s]
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]
module OCEAN / Surface fluxes
real(rp), dimension(:,:), allocatable, public atmos_u
integer, public ie
end point of inner domain: x, local
real(rp), dimension(:,:), allocatable, public atmos_sflx_sw
module ATMOSPHERE / Thermodynamics
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0m
ocean surface roughness length for momentum [m]
real(rp), dimension(:,:), allocatable, public atmos_pbl
real(rp), dimension(:,:), allocatable, public ocean_sflx_sh
ocean surface sensible heat flux [J/m2/s]
module HISTORY
real(rp), dimension(:,:), allocatable, public ocean_sfc_temp
ocean surface skin temperature [K]
module Surface roughness length
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0m_t
tendency of OCEAN_SFC_Z0M
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]
procedure(ocn), pointer, public ocean_phy
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
integer, public ja
of y whole cells (local, with HALO)
Here is the caller graph for this function: