SCALE-RM
scale_roughness.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
11 !-------------------------------------------------------------------------------
12 #include "inc_openmp.h"
14  !-----------------------------------------------------------------------------
15  !
16  !++ used modules
17  !
18  use scale_precision
19  use scale_stdio
20  use scale_prof
22  !-----------------------------------------------------------------------------
23  implicit none
24  private
25  !-----------------------------------------------------------------------------
26  !
27  !++ Public procedure
28  !
29  public :: roughness_setup
30 
31  abstract interface
32  subroutine rl( &
33  Z0M_t, &
34  Z0H_t, &
35  Z0E_t, &
36  Z0M, &
37  Z0H, &
38  Z0E, &
39  UA, &
40  VA, &
41  Z1, &
42  dt )
43  use scale_precision
45  implicit none
46 
47  real(RP), intent(out) :: Z0M_t(IA,JA) ! tendency of roughness length for momentum [m]
48  real(RP), intent(out) :: Z0H_t(IA,JA) ! tendency of roughness length for heat [m]
49  real(RP), intent(out) :: Z0E_t(IA,JA) ! tendency of roughness length for vapor [m]
50 
51  real(RP), intent(in) :: Z0M(IA,JA) ! roughness length for momentum [m]
52  real(RP), intent(in) :: Z0H(IA,JA) ! roughness length for heat [m]
53  real(RP), intent(in) :: Z0E(IA,JA) ! roughness length for vapor [m]
54  real(RP), intent(in) :: UA (IA,JA) ! velocity u at the lowest atmospheric layer [m/s]
55  real(RP), intent(in) :: VA (IA,JA) ! velocity v at the lowest atmospheric layer [m/s]
56  real(RP), intent(in) :: Z1 (IA,JA) ! cell center height at the lowest atmospheric layer [m]
57  real(DP), intent(in) :: dt ! delta time
58  end subroutine rl
59  end interface
60 
61  procedure(rl), pointer :: roughness => null()
62  public :: roughness
63 
64  !-----------------------------------------------------------------------------
65  !
66  !++ Public parameters & variables
67  !
68  !-----------------------------------------------------------------------------
69  !
70  !++ Private procedure
71  !
72  private :: roughness_miller92_setup
73  private :: roughness_moon07_setup
74  private :: roughness_const_setup
75  private :: roughness_miller92
76  private :: roughness_moon07
77  private :: roughness_const
78 
79  !-----------------------------------------------------------------------------
80  !
81  !++ Private parameters & variables
82  !
83  character(len=H_SHORT), private :: roughness_type = 'MOON07' ! surface roughness length scheme
84 
85  real(RP), private :: roughness_visck = 1.5e-5_rp ! kinematic viscosity
86  real(RP), private :: roughness_ustar_min = 1.0e-3_rp ! minimum fiction velocity
87  real(RP), private :: roughness_z0m_min = 1.0e-5_rp ! minimum roughness length for momentum [m]
88  real(RP), private :: roughness_z0h_min = 1.0e-5_rp ! minimum roughness length for heat [m]
89  real(RP), private :: roughness_z0e_min = 1.0e-5_rp ! minimum roughness length for moisture [m]
90 
91  real(RP), private :: roughness_miller92_cm0 = 1.0e-3_rp ! bulk coef. for U*
92  real(RP), private :: roughness_miller92_z0mi = 0.0e-0_rp ! base roughness length for momentum
93  real(RP), private :: roughness_miller92_z0mr = 1.8e-2_rp ! rough factor for momentum
94  real(RP), private :: roughness_miller92_z0ms = 1.1e-1_rp ! smooth factor for momentum
95  real(RP), private :: roughness_miller92_z0hi = 1.4e-5_rp ! base roughness length for heat
96  real(RP), private :: roughness_miller92_z0hr = 0.0e-0_rp ! rough factor for heat
97  real(RP), private :: roughness_miller92_z0hs = 4.0e-1_rp ! smooth factor for heat
98  real(RP), private :: roughness_miller92_z0ei = 1.3e-4_rp ! base roughness length for moisture
99  real(RP), private :: roughness_miller92_z0er = 0.0e-0_rp ! rough factor for moisture
100  real(RP), private :: roughness_miller92_z0es = 6.2e-1_rp ! smooth factor for moisture
101 
102  integer, private :: roughness_moon07_itelim = 10 ! maximum iteration number
103 
104  !-----------------------------------------------------------------------------
105 contains
106  !-----------------------------------------------------------------------------
107  subroutine roughness_setup
108  use scale_process, only: &
110  implicit none
111 
112  namelist / param_roughness / &
113  roughness_type, &
114  roughness_visck, &
115  roughness_ustar_min, &
116  roughness_z0m_min, &
117  roughness_z0h_min, &
118  roughness_z0e_min
119 
120  integer :: ierr
121  !---------------------------------------------------------------------------
122 
123  if( io_l ) write(io_fid_log,*)
124  if( io_l ) write(io_fid_log,*) '++++++ Module[ROUGHNESS] / Categ[COUPLER] / Origin[SCALElib]'
125 
126  !--- read namelist
127  rewind(io_fid_conf)
128  read(io_fid_conf,nml=param_roughness,iostat=ierr)
129  if( ierr < 0 ) then !--- missing
130  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
131  elseif( ierr > 0 ) then !--- fatal error
132  write(*,*) 'xxx Not appropriate names in namelist PARAM_ROUGHNESS. Check!'
133  call prc_mpistop
134  endif
135  if( io_nml ) write(io_fid_nml,nml=param_roughness)
136 
137  if( io_l ) write(io_fid_log,*)
138  if( io_l ) write(io_fid_log,*) '*** Scheme for ocean roughness length : ', trim(roughness_type)
139  select case(roughness_type)
140  case('MILLER92')
141  if( io_l ) write(io_fid_log,*) '*** => Miller (1992)'
142  roughness => roughness_miller92
143  call roughness_miller92_setup
144  case('MOON07')
145  if( io_l ) write(io_fid_log,*) '*** => Moon et al. (2007)'
146  roughness => roughness_moon07
147  call roughness_moon07_setup
148  case('CONST')
149  if( io_l ) write(io_fid_log,*) '*** => Constant.'
150  roughness => roughness_const
151  call roughness_const_setup
152  case default
153  write(*,*) 'xxx Unsupported ROUGHNESS_type. STOP'
154  call prc_mpistop
155  end select
156 
157  return
158  end subroutine roughness_setup
159 
160  !-----------------------------------------------------------------------------
161  subroutine roughness_miller92_setup
162  use scale_process, only: &
164  implicit none
165 
166  namelist / param_roughness_miller92 / &
167  roughness_miller92_cm0, &
168  roughness_miller92_z0mi, &
169  roughness_miller92_z0mr, &
170  roughness_miller92_z0ms, &
171  roughness_miller92_z0hi, &
172  roughness_miller92_z0hr, &
173  roughness_miller92_z0hs, &
174  roughness_miller92_z0ei, &
175  roughness_miller92_z0er, &
176  roughness_miller92_z0es
177 
178  integer :: ierr
179  !---------------------------------------------------------------------------
180 
181  !--- read namelist
182  rewind(io_fid_conf)
183  read(io_fid_conf,nml=param_roughness_miller92,iostat=ierr)
184  if( ierr < 0 ) then !--- missing
185  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
186  elseif( ierr > 0 ) then !--- fatal error
187  write(*,*) 'xxx Not appropriate names in namelist PARAM_ROUGHNESS_MILLER92. Check!'
188  call prc_mpistop
189  endif
190  if( io_nml ) write(io_fid_nml,nml=param_roughness_miller92)
191 
192  return
193  end subroutine roughness_miller92_setup
194 
195  !-----------------------------------------------------------------------------
196  subroutine roughness_moon07_setup
197  use scale_process, only: &
199  implicit none
200 
201  namelist / param_roughness_moon07 / &
202  roughness_moon07_itelim
203 
204  integer :: ierr
205  !---------------------------------------------------------------------------
206 
207  !--- read namelist
208  rewind(io_fid_conf)
209  read(io_fid_conf,nml=param_roughness_moon07,iostat=ierr)
210  if( ierr < 0 ) then !--- missing
211  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
212  elseif( ierr > 0 ) then !--- fatal error
213  write(*,*) 'xxx Not appropriate names in namelist PARAM_ROUGHNESS_MOON07. Check!'
214  call prc_mpistop
215  endif
216  if( io_nml ) write(io_fid_nml,nml=param_roughness_moon07)
217 
218  return
219  end subroutine roughness_moon07_setup
220 
221  !-----------------------------------------------------------------------------
222  subroutine roughness_const_setup
223  implicit none
224  !---------------------------------------------------------------------------
225 
226  return
227  end subroutine roughness_const_setup
228 
229  !-----------------------------------------------------------------------------
230  subroutine roughness_miller92( &
231  Z0M_t, & ! [OUT]
232  Z0H_t, & ! [OUT]
233  Z0E_t, & ! [OUT]
234  Z0M, & ! [IN]
235  Z0H, & ! [IN]
236  Z0E, & ! [IN]
237  UA, & ! [IN]
238  VA, & ! [IN]
239  Z1, & ! [IN]
240  dt ) ! [IN]
241  use scale_const, only: &
242  grav => const_grav
243  implicit none
244 
245  ! arguments
246  real(RP), intent(out) :: z0m_t(ia,ja) ! tendency of roughness length for momentum [m]
247  real(RP), intent(out) :: z0h_t(ia,ja) ! tendency of roughness length for heat [m]
248  real(RP), intent(out) :: z0e_t(ia,ja) ! tendency of roughness length for vapor [m]
249 
250  real(RP), intent(in) :: z0m(ia,ja) ! roughness length for momentum [m]
251  real(RP), intent(in) :: z0h(ia,ja) ! roughness length for heat [m]
252  real(RP), intent(in) :: z0e(ia,ja) ! roughness length for vapor [m]
253  real(RP), intent(in) :: ua (ia,ja) ! velocity u at the lowest atomspheric layer [m/s]
254  real(RP), intent(in) :: va (ia,ja) ! velocity v at the lowest atomspheric layer [m/s]
255  real(RP), intent(in) :: z1 (ia,ja) ! cell center height at the lowest atmospheric layer [m]
256  real(DP), intent(in) :: dt ! delta time
257 
258  ! works
259  real(RP) :: z0m1(ia,ja)
260  real(RP) :: z0h1(ia,ja)
261  real(RP) :: z0e1(ia,ja)
262 
263  real(RP) :: uabs, ustar
264 
265  integer :: i, j
266  !---------------------------------------------------------------------------
267 
268  do j = js, je
269  do i = is, ie
270 
271  uabs = sqrt( ua(i,j)**2 + va(i,j)**2 )
272  ustar = max( sqrt( roughness_miller92_cm0 ) * uabs, roughness_ustar_min )
273 
274  z0m1(i,j) = max( roughness_miller92_z0mi &
275  + roughness_miller92_z0mr / grav * ustar * ustar &
276  + roughness_miller92_z0ms * roughness_visck / ustar, &
277  roughness_z0m_min )
278  z0h1(i,j) = max( roughness_miller92_z0hi &
279  + roughness_miller92_z0hr / grav * ustar * ustar &
280  + roughness_miller92_z0hs * roughness_visck / ustar, &
281  roughness_z0h_min )
282  z0e1(i,j) = max( roughness_miller92_z0ei &
283  + roughness_miller92_z0er / grav * ustar * ustar &
284  + roughness_miller92_z0es * roughness_visck / ustar, &
285  roughness_z0e_min )
286 
287  ! calculate tendency
288  z0m_t(i,j) = ( z0m1(i,j) - z0m(i,j) ) / dt
289  z0h_t(i,j) = ( z0h1(i,j) - z0h(i,j) ) / dt
290  z0e_t(i,j) = ( z0e1(i,j) - z0e(i,j) ) / dt
291 
292  enddo
293  enddo
294 
295  return
296  end subroutine roughness_miller92
297 
298  !-----------------------------------------------------------------------------
302  subroutine roughness_moon07( &
303  Z0M_t, & ! [OUT]
304  Z0H_t, & ! [OUT]
305  Z0E_t, & ! [OUT]
306  Z0M, & ! [IN]
307  Z0H, & ! [IN]
308  Z0E, & ! [IN]
309  UA, & ! [IN]
310  VA, & ! [IN]
311  Z1, & ! [IN]
312  dt ) ! [IN]
313  use scale_const, only: &
314  grav => const_grav, &
315  karman => const_karman
316  implicit none
317 
318  ! arguments
319  real(RP), intent(out) :: z0m_t(ia,ja) ! tendency of roughness length for momentum [m]
320  real(RP), intent(out) :: z0h_t(ia,ja) ! tendency of roughness length for heat [m]
321  real(RP), intent(out) :: z0e_t(ia,ja) ! tendency of roughness length for vapor [m]
322 
323  real(RP), intent(in) :: z0m(ia,ja) ! roughness length for momentum [m]
324  real(RP), intent(in) :: z0h(ia,ja) ! roughness length for heat [m]
325  real(RP), intent(in) :: z0e(ia,ja) ! roughness length for vapor [m]
326  real(RP), intent(in) :: ua (ia,ja) ! velocity u at the lowest atomspheric layer [m/s]
327  real(RP), intent(in) :: va (ia,ja) ! velocity v at the lowest atomspheric layer [m/s]
328  real(RP), intent(in) :: z1 (ia,ja) ! cell center height at the lowest atmospheric layer [m]
329  real(DP), intent(in) :: dt ! delta time
330 
331  ! works
332  real(RP) :: z0m1(ia,ja)
333  real(RP) :: z0h1(ia,ja)
334  real(RP) :: z0e1(ia,ja)
335 
336  real(RP) :: ustar(ia,ja)
337  real(RP) :: uabs (ia,ja)
338  real(RP) :: u10m
339 
340  integer :: ite
341  integer :: i, j
342  !---------------------------------------------------------------------------
343 
344  do j = js, je
345  do i = is, ie
346  z0m1(i,j) = max( z0m(i,j), roughness_z0m_min )
347  uabs(i,j) = sqrt( ua(i,j)**2 + va(i,j)**2 )
348  enddo
349  enddo
350 
351  do ite = 1, roughness_moon07_itelim
352  !$omp parallel do default(none) &
353  !$omp shared(JS,JE,IS,IE,Ustar,Z0M1,Uabs,Z1,ROUGHNESS_Ustar_min,GRAV,ROUGHNESS_Z0M_min) &
354  !$omp private(i,j,U10M) OMP_SCHEDULE_
355  do j = js, je
356  do i = is, ie
357  ustar(i,j) = max( karman * uabs(i,j) / log( z1(i,j)/z0m1(i,j) ), roughness_ustar_min )
358  u10m = ustar(i,j) / karman * log( 10.0_rp/z0m1(i,j) )
359 
360  if ( u10m <= 12.5_rp ) then
361  z0m1(i,j) = max( 0.0185_rp * ustar(i,j)**2 / grav, roughness_z0m_min )
362  else
363  z0m1(i,j) = 1.0e-3_rp * ( 0.085_rp * ( -0.56_rp*ustar(i,j)**2 &
364  + 20.255_rp*ustar(i,j) &
365  + 2.458_rp ) - 0.58_rp )
366  endif
367  enddo
368  enddo
369  enddo
370 
371  ! Fairall et al. TOGA V3.0
372  ! Fairall et al. (2003) JCLI, vol. 16, 571-591. Eq. (28)
373  do j = js, je
374  do i = is, ie
375  z0h1(i,j) = min( 5.5e-5_rp / ( z0m1(i,j) * ustar(i,j) / roughness_visck )**0.6_rp, 1.1e-4_rp )
376  z0e1(i,j) = z0h1(i,j)
377  enddo
378  enddo
379 
380  do j = js, je
381  do i = is, ie
382  ! limiter
383  z0m1(i,j) = max( z0m1(i,j), roughness_z0m_min )
384  z0h1(i,j) = max( z0h1(i,j), roughness_z0h_min )
385  z0e1(i,j) = max( z0e1(i,j), roughness_z0e_min )
386 
387  ! calculate tendency
388  z0m_t(i,j) = ( z0m1(i,j) - z0m(i,j) ) / dt
389  z0h_t(i,j) = ( z0h1(i,j) - z0h(i,j) ) / dt
390  z0e_t(i,j) = ( z0e1(i,j) - z0e(i,j) ) / dt
391  enddo
392  enddo
393 
394  return
395  end subroutine roughness_moon07
396 
397  !-----------------------------------------------------------------------------
398  subroutine roughness_const( &
399  Z0M_t, & ! [OUT]
400  Z0H_t, & ! [OUT]
401  Z0E_t, & ! [OUT]
402  Z0M, & ! [IN]
403  Z0H, & ! [IN]
404  Z0E, & ! [IN]
405  UA, & ! [IN]
406  VA, & ! [IN]
407  Z1, & ! [IN]
408  dt ) ! [IN]
409  implicit none
410 
411  ! arguments
412  real(RP), intent(out) :: z0m_t(ia,ja) ! tendency of roughness length for momentum [m]
413  real(RP), intent(out) :: z0h_t(ia,ja) ! tendency of roughness length for heat [m]
414  real(RP), intent(out) :: z0e_t(ia,ja) ! tendency of roughness length for vapor [m]
415 
416  real(RP), intent(in) :: z0m(ia,ja) ! roughness length for momentum [m]
417  real(RP), intent(in) :: z0h(ia,ja) ! roughness length for heat [m]
418  real(RP), intent(in) :: z0e(ia,ja) ! roughness length for vapor [m]
419  real(RP), intent(in) :: ua (ia,ja) ! velocity u at the lowest atomspheric layer [m/s]
420  real(RP), intent(in) :: va (ia,ja) ! velocity v at the lowest atomspheric layer [m/s]
421  real(RP), intent(in) :: z1 (ia,ja) ! cell center height at the lowest atmospheric layer [m]
422  real(DP), intent(in) :: dt ! delta time
423 
424  z0m_t(:,:) = 0.0_rp
425  z0h_t(:,:) = 0.0_rp
426  z0e_t(:,:) = 0.0_rp
427 
428  return
429  end subroutine roughness_const
430 
431 end module scale_roughness
integer, public is
start point of inner domain: x, local
integer, public je
end point of inner domain: y, local
subroutine, public prc_mpistop
Abort MPI.
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:61
subroutine, public roughness_setup
module STDIO
Definition: scale_stdio.F90:12
real(rp), parameter, public const_karman
von Karman constant
Definition: scale_const.F90:52
module grid index
logical, public io_nml
output log or not? (for namelist, this process)
Definition: scale_stdio.F90:62
integer, public ia
of whole cells: x, local, with HALO
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:48
integer, public js
start point of inner domain: y, local
procedure(rl), pointer, public roughness
module PROCESS
module CONSTANT
Definition: scale_const.F90:14
module profiler
Definition: scale_prof.F90:10
integer, public ie
end point of inner domain: x, local
module PRECISION
module Surface roughness length
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
integer, public io_fid_nml
Log file ID (only for output namelist)
Definition: scale_stdio.F90:57
integer, public ja
of whole cells: y, local, with HALO