SCALE-RM
mod_ocean_driver.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
9 !-------------------------------------------------------------------------------
11  !-----------------------------------------------------------------------------
12  !
13  !++ used modules
14  !
15  use scale_precision
16  use scale_stdio
17  use scale_prof
18  use scale_debug
20 
21  use scale_const, only: &
22  i_sw => const_i_sw, &
23  i_lw => const_i_lw
24  !-----------------------------------------------------------------------------
25  implicit none
26  private
27  !-----------------------------------------------------------------------------
28  !
29  !++ Public procedure
30  !
31  public :: ocean_driver_setup
32  public :: ocean_driver_resume
33  public :: ocean_driver
34  public :: ocean_surface_get
35  public :: ocean_surface_set
36 
37  !-----------------------------------------------------------------------------
38  !
39  !++ Public parameters & variables
40  !
41  !-----------------------------------------------------------------------------
42  !
43  !++ Private procedure
44  !
45  !-----------------------------------------------------------------------------
46  !
47  !++ Private parameters & variables
48  !
49  !-----------------------------------------------------------------------------
50 contains
51  !-----------------------------------------------------------------------------
53  subroutine ocean_driver_setup
54  use mod_ocean_phy_driver, only: &
56 ! use mod_ocean_frc_nudge, only: &
57 ! OCEAN_FRC_driver_setup
58  implicit none
59  !---------------------------------------------------------------------------
60 
61  if( io_l ) write(io_fid_log,*)
62  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[OCEAN] / Origin[SCALE-RM]'
63 
65 
66 ! if( OCEAN_FRC_sw ) call OCEAN_FRC_driver_setup
67 
68  return
69  end subroutine ocean_driver_setup
70 
71  !-----------------------------------------------------------------------------
73  subroutine ocean_driver_resume
74  use mod_ocean_phy_driver, only: &
76 ! use mod_ocean_frc_nudge, only: &
77 ! OCEAN_FRC_driver_resume
78  use mod_ocean_vars, only: &
80  use mod_ocean_admin, only: &
81  ocean_sw
82  implicit none
83  !---------------------------------------------------------------------------
84 
85  if( io_l ) write(io_fid_log,*)
86  if( io_l ) write(io_fid_log,*) '++++++ Module[DRIVER] / Categ[OCEAN] / Origin[SCALE-RM]'
87 
88  !########## Get Surface Boundary from coupler ##########
90 
92 
93 ! if( OCEAN_FRC_sw ) call OCEAN_FRC_driver_resume
94 
95  !########## Set Surface Boundary to coupler ##########
96  call ocean_surface_set( countup=.true. )
97 
98  !########## History & Monitor ##########
99  if ( ocean_sw ) then
100  call prof_rapstart('OCN_History', 1)
101  call ocean_vars_history
102  call prof_rapend ('OCN_History', 1)
103  endif
104 
105  return
106  end subroutine ocean_driver_resume
107 
108  !-----------------------------------------------------------------------------
110  subroutine ocean_driver
111  use scale_time, only: &
112  dt => time_dtsec_ocean
113  use mod_ocean_admin, only: &
114  ocean_sw
115  use mod_ocean_vars, only: &
116  ocean_temp, &
117  ocean_sfc_temp, &
119  ocean_sfc_z0m, &
120  ocean_sfc_z0h, &
121  ocean_sfc_z0e, &
122  ocean_temp_t, &
125  ocean_sfc_z0m_t, &
126  ocean_sfc_z0h_t, &
127  ocean_sfc_z0e_t, &
130  use mod_ocean_phy_driver, only: &
132 ! use mod_ocean_forcing, only: &
133 ! OCEAN_forcing
134  implicit none
135 
136  integer :: i, j
137  !---------------------------------------------------------------------------
138 
139  !########## Get Surface Boundary from coupler ##########
140  call prof_rapstart('OCN_SfcExch', 2)
141  call ocean_surface_get
142  call prof_rapend ('OCN_SfcExch', 2)
143 
144  !########## Physics ##########
145  if ( ocean_sw ) then
146  call prof_rapstart('OCN_Physics', 1)
147  call ocean_phy_driver( update_flag = .true. )
148  call prof_rapend ('OCN_Physics', 1)
149  endif
150 
151  !########## Forcing ##########
152 ! if ( OCEAN_FORCE_sw ) then
153 ! call PROF_rapstart('OCN_Forcing', 1)
154 ! call OCEAN_forcing
155 ! call PROF_rapend ('OCN_Forcing', 1)
156 ! endif
157 
158  !########## Update ##########
159  do j = js, je
160  do i = is, ie
161  ocean_temp(i,j) = ocean_temp(i,j) + ocean_temp_t(i,j) * dt
162  ocean_sfc_temp(i,j) = ocean_sfc_temp(i,j) + ocean_sfc_temp_t(i,j) * dt
163  ocean_sfc_albedo(i,j,i_lw) = ocean_sfc_albedo(i,j,i_lw) + ocean_sfc_albedo_t(i,j,i_lw) * dt
164  ocean_sfc_albedo(i,j,i_sw) = ocean_sfc_albedo(i,j,i_sw) + ocean_sfc_albedo_t(i,j,i_sw) * dt
165  ocean_sfc_z0m(i,j) = ocean_sfc_z0m(i,j) + ocean_sfc_z0m_t(i,j) * dt
166  ocean_sfc_z0h(i,j) = ocean_sfc_z0h(i,j) + ocean_sfc_z0h_t(i,j) * dt
167  ocean_sfc_z0e(i,j) = ocean_sfc_z0e(i,j) + ocean_sfc_z0e_t(i,j) * dt
168  enddo
169  enddo
170 
171  call ocean_vars_total
172 
173  !########## Set Surface Boundary to coupler ##########
174  call prof_rapstart('OCN_SfcExch', 2)
175  call ocean_surface_set( countup=.true. )
176  call prof_rapend ('OCN_SfcExch', 2)
177 
178  !########## reset tendencies ##########
179 !OCL XFILL
180  do j = js, je
181  do i = is, ie
182  ocean_temp_t(i,j) = 0.0_rp
183  ocean_sfc_temp_t(i,j) = 0.0_rp
184  ocean_sfc_albedo_t(i,j,i_lw) = 0.0_rp
185  ocean_sfc_albedo_t(i,j,i_sw) = 0.0_rp
186  ocean_sfc_z0m_t(i,j) = 0.0_rp
187  ocean_sfc_z0h_t(i,j) = 0.0_rp
188  ocean_sfc_z0e_t(i,j) = 0.0_rp
189  enddo
190  enddo
191 
192  !########## History & Monitor ##########
193  call prof_rapstart('OCN_History', 1)
194  call ocean_vars_history
195  call prof_rapend ('OCN_History', 1)
196 
197  return
198  end subroutine ocean_driver
199 
200  !-----------------------------------------------------------------------------
202  subroutine ocean_surface_get
203  use mod_ocean_admin, only: &
204  ocean_sw
205  use mod_ocean_vars, only: &
206  atmos_temp, &
207  atmos_pres, &
208  atmos_w, &
209  atmos_u, &
210  atmos_v, &
211  atmos_dens, &
212  atmos_qv, &
213  atmos_pbl, &
214  atmos_sfc_pres, &
215  atmos_sflx_lw, &
216  atmos_sflx_sw, &
217  atmos_cossza, &
219  use mod_cpl_vars, only: &
221  implicit none
222 
223  real(RP) :: ATMOS_SFLX_rad_dn(ia,ja,2,2)
224  real(RP) :: ATMOS_SFLX_rain (ia,ja)
225  real(RP) :: ATMOS_SFLX_snow (ia,ja)
226  !---------------------------------------------------------------------------
227 
228  if ( ocean_sw ) then
229  call cpl_getatm_ocn( atmos_temp(:,:), & ! [OUT]
230  atmos_pres(:,:), & ! [OUT]
231  atmos_w(:,:), & ! [OUT]
232  atmos_u(:,:), & ! [OUT]
233  atmos_v(:,:), & ! [OUT]
234  atmos_dens(:,:), & ! [OUT]
235  atmos_qv(:,:), & ! [OUT]
236  atmos_pbl(:,:), & ! [OUT]
237  atmos_sfc_pres(:,:), & ! [OUT]
238  atmos_sflx_rad_dn(:,:,:,:), & ! [OUT]
239  atmos_cossza(:,:), & ! [OUT]
240  atmos_sflx_rain(:,:), & ! [OUT]
241  atmos_sflx_snow(:,:) ) ! [OUT]
242  endif
243 
244  atmos_sflx_sw(:,:) = atmos_sflx_rad_dn(:,:,i_sw,1) + atmos_sflx_rad_dn(:,:,i_sw,2) ! direct+diffuse
245  atmos_sflx_lw(:,:) = atmos_sflx_rad_dn(:,:,i_lw,1) + atmos_sflx_rad_dn(:,:,i_lw,2) ! direct+diffuse
246 
247  atmos_sflx_prec(:,:) = atmos_sflx_rain(:,:) + atmos_sflx_snow(:,:) ! liquid+ice
248 
249  return
250  end subroutine ocean_surface_get
251 
252  !-----------------------------------------------------------------------------
254  subroutine ocean_surface_set( countup )
255  use mod_ocean_admin, only: &
256  ocean_sw
257  use mod_ocean_vars, only: &
258  ocean_sfc_temp, &
260  ocean_sfc_z0m, &
261  ocean_sfc_z0h, &
262  ocean_sfc_z0e, &
263  ocean_sflx_mw, &
264  ocean_sflx_mu, &
265  ocean_sflx_mv, &
266  ocean_sflx_sh, &
267  ocean_sflx_lh, &
268  ocean_sflx_wh, &
269  ocean_sflx_evap, &
270  ocean_u10, &
271  ocean_v10, &
272  ocean_t2, &
273  ocean_q2
274  use mod_cpl_vars, only: &
275  cpl_putocn
276  implicit none
277 
278  ! arguments
279  logical, intent(in) :: countup
280  !---------------------------------------------------------------------------
281 
282  if ( ocean_sw ) then
283  call cpl_putocn( ocean_sfc_temp(:,:), & ! [IN]
284  ocean_sfc_albedo(:,:,:), & ! [IN]
285  ocean_sfc_z0m(:,:), & ! [IN]
286  ocean_sfc_z0h(:,:), & ! [IN]
287  ocean_sfc_z0e(:,:), & ! [IN]
288  ocean_sflx_mw(:,:), & ! [IN]
289  ocean_sflx_mu(:,:), & ! [IN]
290  ocean_sflx_mv(:,:), & ! [IN]
291  ocean_sflx_sh(:,:), & ! [IN]
292  ocean_sflx_lh(:,:), & ! [IN]
293  ocean_sflx_wh(:,:), & ! [IN]
294  ocean_sflx_evap(:,:), & ! [IN]
295  ocean_u10(:,:), & ! [IN]
296  ocean_v10(:,:), & ! [IN]
297  ocean_t2(:,:), & ! [IN]
298  ocean_q2(:,:), & ! [IN]
299  countup ) ! [IN]
300  endif
301 
302  return
303  end subroutine ocean_surface_set
304 
305 end module mod_ocean_driver
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
module DEBUG
Definition: scale_debug.F90:13
logical, public ocean_sw
real(rp), dimension(:,:), allocatable, public atmos_w
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 ocean_driver_setup
Setup.
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]
real(rp), dimension(:,:), allocatable, public atmos_v
subroutine, public ocean_vars_history
History output set for ocean variables.
subroutine, public ocean_surface_get
Get surface boundary from other model.
module STDIO
Definition: scale_stdio.F90:12
real(rp), dimension(:,:), allocatable, public ocean_sflx_wh
ocean surface water heat flux [J/m2/s]
module OCEAN / Physics
real(rp), dimension(:,:), allocatable, public atmos_sflx_lw
real(rp), dimension(:,:), allocatable, public ocean_temp_t
tendency of OCEAN_TEMP
module grid index
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]
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_WH, SFLX_evap, U10, V10, T2, Q2, countup)
module OCEAN driver
subroutine, public ocean_surface_set(countup)
Put surface boundary to other model.
real(rp), dimension(:,:), allocatable, public atmos_sfc_pres
real(rp), dimension(:,:), allocatable, public atmos_qv
module COUPLER Variables
subroutine, public ocean_vars_total
Budget monitor for ocean.
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0h_t
tendency of OCEAN_SFC_Z0H
subroutine, public ocean_driver_resume
Resume.
integer, public js
start point of inner domain: y, local
module TIME
Definition: scale_time.F90:15
real(rp), dimension(:,:), allocatable, public atmos_sflx_prec
module Ocean admin
subroutine, public ocean_driver
Ocean step.
real(rp), dimension(:,:), allocatable, public atmos_temp
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 prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:132
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]
subroutine, public cpl_getatm_ocn(TEMP, PRES, W, U, V, DENS, QV, PBL, SFC_PRES, SFLX_rad_dn, cosSZA, SFLX_rain, SFLX_snow)
real(rp), dimension(:,:), allocatable, public atmos_pbl
integer, public const_i_sw
short-wave radiation index
Definition: scale_const.F90:99
module PRECISION
real(rp), dimension(:,:), allocatable, public ocean_sflx_sh
ocean surface sensible heat flux [J/m2/s]
subroutine, public ocean_phy_driver(update_flag)
Driver.
real(rp), dimension(:,:), allocatable, public ocean_sfc_temp
ocean surface skin temperature [K]
real(rp), dimension(:,:), allocatable, public ocean_sfc_z0m_t
tendency of OCEAN_SFC_Z0M
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
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]
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:178
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
subroutine, public ocean_phy_driver_setup
Setup.
subroutine, public ocean_phy_driver_resume
Resume.
integer, public ja
of y whole cells (local, with HALO)