SCALE-RM
Functions/Subroutines | Variables
scale_atmos_phy_mp_suzuki10 Module Reference

module Spectran Bin Microphysics More...

Functions/Subroutines

subroutine, public atmos_phy_mp_suzuki10_tracer_setup
 Config. More...
 
subroutine, public atmos_phy_mp_suzuki10_setup (KA, IA, JA, flg_lt)
 Setup. More...
 
subroutine, public atmos_phy_mp_suzuki10_finalize
 finalize More...
 
subroutine, public atmos_phy_mp_suzuki10_tendency (KA, KS, KE, IA, IS, IE, JA, JS, JE, KIJMAX, dt, DENS, PRES, TEMP, QTRC, QDRY, CPtot, CVtot, CCN, RHOQ_t, RHOE_t, CPtot_t, CVtot_t, EVAPORATE, flg_lt, d0_crg, v0_crg, dqcrg, beta_crg, QTRC_crg, QSPLT_in, Sarea, RHOC_t_mp)
 Cloud Microphysics. More...
 
subroutine, public atmos_phy_mp_suzuki10_terminal_velocity (KA, vterm_o)
 get terminal velocity More...
 
subroutine, public atmos_phy_mp_suzuki10_cloud_fraction (KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC0, mask_criterion, cldfrac)
 Calculate Cloud Fraction. More...
 
subroutine, public atmos_phy_mp_suzuki10_effective_radius (KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS0, TEMP0, QTRC0, Re)
 Calculate Effective Radius. More...
 
subroutine, public atmos_phy_mp_suzuki10_qtrc2qhyd (KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC0, Qe)
 Calculate mass ratio of each category. More...
 
subroutine, public atmos_phy_mp_suzuki10_qtrc2nhyd (KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS, QTRC0, Ne)
 Calculate number concentration of each category. More...
 
subroutine, public atmos_phy_mp_suzuki10_qhyd2qtrc (KA, KS, KE, IA, IS, IE, JA, JS, JE, Qe, QTRC, QNUM)
 get mass ratio of each category More...
 
subroutine, public atmos_phy_mp_suzuki10_crg_qtrc2qhyd (KA, KS, KE, IA, IS, IE, JA, JS, JE, QTRC0, Qecrg)
 get charge density ratio of each category More...
 

Variables

integer, public atmos_phy_mp_suzuki10_ntracers
 
integer, public atmos_phy_mp_suzuki10_nwaters
 
integer, public atmos_phy_mp_suzuki10_nices
 
integer, public atmos_phy_mp_suzuki10_nccn
 
integer, public atmos_phy_mp_suzuki10_nbnd
 
character(len=h_short), dimension(:), allocatable, public atmos_phy_mp_suzuki10_tracer_names
 
character(len=h_mid), dimension(:), allocatable, public atmos_phy_mp_suzuki10_tracer_descriptions
 
character(len=h_short), dimension(:), allocatable, public atmos_phy_mp_suzuki10_tracer_units
 
integer, public nbin = 33
 
integer, public nccn = 0
 

Detailed Description

module Spectran Bin Microphysics

Description:
This module contains subroutines for the Spectral Bin Model
Author
: Team SCALE
NAMELIST
  • PARAM_ATMOS_PHY_MP_SUZUKI10_bin
    nametypedefault valuecomment
    NBIN integer 33 tentatively public
    NCCN integer 0 tentatively public
    ICEFLG integer 1
    KPHASE integer 0

  • PARAM_ATMOS_PHY_MP_SUZUKI10
    nametypedefault valuecomment
    MP_DOAUTOCONVERSION logical .true. apply collision process ?
    MP_COUPLE_AEROSOL logical .false. apply CCN effect?
    RHO_AERO real(RP) — density of aerosol
    R_MIN real(RP) — minimum radius of aerosol (um)
    R_MAX real(RP) — maximum radius of aerosol (um)
    R0_AERO real(RP) — center radius of aerosol (um)
    S10_EMAER real(RP) — moleculer weight of aerosol
    S10_FLAG_REGENE logical .false. — flag of regeneration
    S10_FLAG_NUCLEAT logical .false. — flag of regeneration
    S10_FLAG_ICENUCLEAT logical .false. — flag of ice nucleation
    S10_FLAG_SFAERO logical .false. — flag of surface flux of aeorol
    S10_FLAG_RNDM logical .false. — flag for sthastic integration for coll.-coag.
    S10_RNDM_MSPC integer
    S10_RNDM_MBIN integer
    C_CCN real(RP) 100.E+6_RP N0 of Nc = N0*s^kappa
    KAPPA real(RP) 0.462_RP kappa of Nc = N0*s^kappa
    N0_ICENUCL real(RP) 1.E+3_RP N0 of Meyer et al. (1992)
    SIGMA real(RP) 7.5E-02_RP water surface tension N/m2
    VHFCT real(RP) 2.0_RP van't hoff factor (i in eq.(A.11) of Suzuki (2004))
    ECOAL_GSI real(RP) 0.0_RP

History Output
No history output

Function/Subroutine Documentation

◆ atmos_phy_mp_suzuki10_tracer_setup()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_tracer_setup

Config.

Definition at line 300 of file scale_atmos_phy_mp_suzuki10.F90.

300  use scale_prc, only: &
301  prc_abort
302  implicit none
303 
304  namelist / param_atmos_phy_mp_suzuki10_bin / &
305  nbin, &
306  nccn, &
307  iceflg, &
308  kphase
309 
310  integer :: m, n, ierr
311  !---------------------------------------------------------------------------
312 
313  log_newline
314  log_info("ATMOS_PHY_MP_suzuki10_tracer_setup",*) 'Setup'
315  log_info("ATMOS_PHY_MP_suzuki10_tracer_setup",*) 'Tracers setup for Suzuki (2010) Spectral BIN model'
316 
317  log_newline
318  log_info("ATMOS_PHY_MP_suzuki10_tracer_setup",*) 'READ BIN NUMBER'
319 
320  rewind(io_fid_conf)
321  read(io_fid_conf,nml=param_atmos_phy_mp_suzuki10_bin,iostat=ierr)
322 
323  if( ierr < 0 ) then !--- missing
324  log_info("ATMOS_PHY_MP_suzuki10_tracer_setup",*) 'Not found namelist. Default used.'
325  elseif( ierr > 0 ) then !--- fatal error
326  log_error("ATMOS_PHY_MP_suzuki10_tracer_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_MP_SUZUKI10_bin, Check!'
327  call prc_abort
328  end if
329 
330  log_nml(param_atmos_phy_mp_suzuki10_bin)
331 
332  if( iceflg == 0 ) then
333  nspc = 1
334  elseif( iceflg == 1 ) then
335  nspc = 7
336  else
337  log_error("ATMOS_PHY_MP_suzuki10_tracer_setup",*) "ICEFLG should be 0 (warm rain) or 1 (mixed rain) check!!"
338  call prc_abort
339  endif
340 
341  atmos_phy_mp_suzuki10_ntracers = 1 + nbin*nspc + nccn ! number of total tracers
342  atmos_phy_mp_suzuki10_nwaters = nbin ! number of liquid water
343  atmos_phy_mp_suzuki10_nices = nbin * ( nspc - 1 ) ! number of ice water
344  atmos_phy_mp_suzuki10_nccn = nccn ! number of ccn
345 
346  num_hyd = nbin * nspc
347 
348  num_start_waters = i_qv + 1
349  num_end_waters = i_qv + atmos_phy_mp_suzuki10_nwaters
350  num_start_ices = num_end_waters + 1
351  num_end_ices = num_end_waters + atmos_phy_mp_suzuki10_nices
352 
353  qa = atmos_phy_mp_suzuki10_ntracers
354 
355  allocate( atmos_phy_mp_suzuki10_tracer_names(qa) )
356  allocate( atmos_phy_mp_suzuki10_tracer_descriptions(qa) )
357  allocate( atmos_phy_mp_suzuki10_tracer_units(qa) )
358 
359  !---------------------------------------------------------------------------
360  !
361  !++ calculate each category and aerosol
362  !
363  !---------------------------------------------------------------------------
364 
365  do n = 1, qa
366  write(atmos_phy_mp_suzuki10_tracer_units(n),'(a)') 'kg/kg'
367  enddo
368 
369  write(atmos_phy_mp_suzuki10_tracer_names(1),'(a)') 'QV'
370  write(atmos_phy_mp_suzuki10_tracer_descriptions(1),'(a)') 'Water Vapor mixing ratio'
371 
372  do m = 1, nspc
373  do n = 1, nbin
374  write(atmos_phy_mp_suzuki10_tracer_names(1+nbin*(m-1)+n),'(a,i0)') trim(namspc(m)), n
375  write(atmos_phy_mp_suzuki10_tracer_descriptions(1+nbin*(m-1)+n),'(a,i0)') trim(lnamspc(m)), n
376  enddo
377  enddo
378 
379  do n = 1, nccn
380  write(atmos_phy_mp_suzuki10_tracer_names(1+nbin*nspc+n),'(a,i0)') trim(namspc(8)), n
381  write(atmos_phy_mp_suzuki10_tracer_descriptions(1+nbin*nspc+n),'(a,i0)') trim(lnamspc(8)), n
382  enddo
383 
384  !$acc update device(QA)
385 
386  return

References atmos_phy_mp_suzuki10_nccn, atmos_phy_mp_suzuki10_nices, atmos_phy_mp_suzuki10_ntracers, atmos_phy_mp_suzuki10_nwaters, atmos_phy_mp_suzuki10_tracer_descriptions, atmos_phy_mp_suzuki10_tracer_names, atmos_phy_mp_suzuki10_tracer_units, scale_io::io_fid_conf, nbin, nccn, and scale_prc::prc_abort().

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_tracer_setup().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_setup()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_setup ( integer, intent(in)  KA,
integer, intent(in)  IA,
integer, intent(in)  JA,
logical, intent(in), optional  flg_lt 
)

Setup.

Definition at line 394 of file scale_atmos_phy_mp_suzuki10.F90.

394  use scale_prc, only: &
395  prc_abort, &
396  prc_masterrank, &
398  use scale_const, only: &
399  pi => const_pi, &
400  dwatr => const_dwatr, &
401  dice => const_dice
402  use scale_comm_cartesc, only: &
403  comm_bcast
404  use scale_atmos_hydrometeor, only: &
405  i_hc, &
406  i_hr, &
407  i_hi, &
408  i_hs, &
409  i_hg, &
410  i_hh
411  implicit none
412 
413  integer, intent(in) :: KA
414  integer, intent(in) :: IA
415  integer, intent(in) :: JA
416  logical, intent(in), optional :: flg_lt
417 
418  real(RP) :: RHO_AERO !--- density of aerosol
419  real(RP) :: R0_AERO !--- center radius of aerosol (um)
420  real(RP) :: R_MIN !--- minimum radius of aerosol (um)
421  real(RP) :: R_MAX !--- maximum radius of aerosol (um)
422  real(RP) :: S10_EMAER !--- moleculer weight of aerosol
423 
424  logical :: S10_FLAG_REGENE = .false. !--- flag of regeneration
425  logical :: S10_FLAG_NUCLEAT = .false. !--- flag of regeneration
426  logical :: S10_FLAG_ICENUCLEAT = .false. !--- flag of ice nucleation
427  logical :: S10_FLAG_SFAERO = .false. !--- flag of surface flux of aeorol
428  logical :: S10_FLAG_RNDM = .false. !--- flag for sthastic integration for coll.-coag.
429  integer :: S10_RNDM_MSPC
430  integer :: S10_RNDM_MBIN
431 
432  namelist / param_atmos_phy_mp_suzuki10 / &
433  mp_doautoconversion, &
434  mp_couple_aerosol, &
435  rho_aero, &
436  r_min, &
437  r_max, &
438  r0_aero, &
439  s10_emaer, &
440  s10_flag_regene, &
441  s10_flag_nucleat, &
442  s10_flag_icenucleat, &
443  s10_flag_sfaero, &
444  s10_flag_rndm, &
445  s10_rndm_mspc, &
446  s10_rndm_mbin, &
447  c_ccn, kappa, &
448  n0_icenucl, &
449  sigma, vhfct, &
450  ecoal_gsi
451 
452  real(RP), parameter :: max_term_vel = 10.0_rp !-- terminal velocity for calculate dt of sedimentation
453 
454  logical :: flg_lt_
455  integer :: nnspc, nnbin
456  integer :: nn, mm, mmyu, nnyu
457  integer :: myu, nyu, i, j, k, n, ierr
458  !---------------------------------------------------------------------------
459 
460  log_newline
461  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'Setup'
462  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'Suzuki (2010) Spectral BIN model'
463 
464  !--- allocation
465  allocate( xctr( nbin ) )
466  allocate( xbnd( nbin+1 ) )
467  allocate( radc( nbin ) )
468  allocate( cctr( nbin,nspc_mk ) )
469  allocate( cbnd( nbin+1,nspc_mk ) )
470  allocate( ck( nspc_mk,nspc_mk,nbin,nbin ) )
471  allocate( vt( nspc_mk,nbin ) )
472  allocate( br( nspc_mk,nbin ) )
473  allocate( ifrsl( 2,nspc_mk,nspc_mk ) )
474  allocate( expxctr( nbin ) )
475  allocate( expxbnd( nbin+1 ) )
476  allocate( rexpxctr( nbin ) )
477  allocate( rexpxbnd( nbin+1 ) )
478  if ( nccn /= 0 ) then
479  allocate( xactr( nccn ) )
480  allocate( xabnd( nccn+1 ) )
481  allocate( rada( nccn ) )
482  allocate( expxactr( nccn ) )
483  allocate( expxabnd( nccn+1 ) )
484  allocate( rexpxactr( nccn ) )
485  allocate( rexpxabnd( nccn+1 ) )
486  endif
487 
488  mbin = nbin/2
489  mspc = nspc_mk*nspc_mk
490 
491  rho_aero = rhoa
492  s10_emaer = emaer
493  r_min = rasta
494  r_max = raend
495  r0_aero = r0a
496  s10_rndm_mspc = mspc
497  s10_rndm_mbin = mbin
498 
499  rewind(io_fid_conf)
500  read(io_fid_conf,nml=param_atmos_phy_mp_suzuki10,iostat=ierr)
501 
502  if ( ierr < 0 ) then !--- missing
503  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'Not found namelist. Default used.'
504  elseif( ierr > 0 ) then !--- fatal error
505  log_error("ATMOS_PHY_MP_suzuki10_setup",*) 'Not appropriate names in namelist PARAM_ATMOS_PHY_MP_SUZUKI10, Check!'
506  call prc_abort
507  endif
508  log_nml(param_atmos_phy_mp_suzuki10)
509 
510  if ( nspc /= 1 .AND. nspc /= 7 ) then
511  log_error("ATMOS_PHY_MP_suzuki10_setup",*) 'nspc should be set as 1 (warm rain) or 7 (mixed phase) check!'
512  call prc_abort
513  endif
514 
515  rhoa = rho_aero
516  emaer = s10_emaer
517  rasta = r_min
518  raend = r_max
519  r0a = r0_aero
520  flg_regeneration = s10_flag_regene
521  flg_nucl = s10_flag_nucleat
522  flg_icenucl = s10_flag_icenucleat
523  flg_sf_aero = s10_flag_sfaero
524  flg_rndm = s10_flag_rndm
525  mspc = s10_rndm_mspc
526  mbin = s10_rndm_mbin
527 
528  !--- read micpara.dat (microphysical parameter) and broad cast
529  if ( prc_ismaster ) then
530 
531  fid_micpara = io_get_available_fid()
532  !--- open parameter of cloud microphysics
533  open ( fid_micpara, file = fname_micpara, form = 'formatted', status = 'old', iostat=ierr )
534 
535  !--- micpara.dat does not exist
536  if ( ierr == 0 ) then
537 
538  read( fid_micpara,* ) nnspc, nnbin
539 
540  if ( nnbin /= nbin ) then
541  log_error("ATMOS_PHY_MP_suzuki10_setup",*) 'nbin in namelist and nbin in micpara.dat is different check!'
542  call prc_abort
543  endif
544 
545  ! grid parameter
546  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'Radius of cloud *'
547  do n = 1, nbin
548  read( fid_micpara,* ) nn, xctr( n ), radc( n )
549  log_info("ATMOS_PHY_MP_suzuki10_setup",'(A,1x,I3,1x,A,1x,ES15.7,1x,A)') &
550  "Radius of ", n, "th cloud bin (bin center)= ", radc( n ) , "[m]"
551  enddo
552  do n = 1, nbin+1
553  read( fid_micpara,* ) nn, xbnd( n )
554  enddo
555  read( fid_micpara,* ) dxmic
556  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'Width of Cloud SDF= ', dxmic
557 
558  ! capacity
559  do myu = 1, nspc_mk
560  do n = 1, nbin
561 ! read( fid_micpara,* ) mmyu, nn, cctr( myu,n )
562  read( fid_micpara,* ) mmyu, nn, cctr( n,myu )
563  enddo
564  do n = 1, nbin+1
565 ! read( fid_micpara,* ) mmyu, nn, cbnd( myu,n )
566  read( fid_micpara,* ) mmyu, nn, cbnd( n,myu )
567  enddo
568  enddo
569 
570  ! collection kernel
571  do myu = 1, nspc_mk
572  do nyu = 1, nspc_mk
573  do i = 1, nbin
574  do j = 1, nbin
575  read( fid_micpara,* ) mmyu, nnyu, mm, nn, ck( myu,nyu,i,j )
576  enddo
577  enddo
578  enddo
579  enddo
580 
581  ! terminal velocity
582  do myu = 1, nspc_mk
583  do n = 1, nbin
584  read( fid_micpara,* ) mmyu, nn, vt( myu,n )
585  enddo
586  enddo
587 
588  ! bulk density
589  do myu = 1, nspc_mk
590  do n = 1, nbin
591  read( fid_micpara,* ) mmyu, nn, br( myu,n )
592  enddo
593  enddo
594 
595  close ( fid_micpara )
596 
597  !--- micpara.dat does not exist
598  else
599 
600  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'micpara.dat is created'
601  call mkpara
602 
603  fid_micpara = io_get_available_fid()
604  !--- open parameter of cloud microphysics
605  open ( fid_micpara, file = fname_micpara, form = 'formatted', status = 'old', iostat=ierr )
606 
607  read( fid_micpara,* ) nnspc, nnbin
608 
609  if ( nnbin /= nbin ) then
610  log_error("ATMOS_PHY_MP_suzuki10_setup",*) 'nbin in inc_tracer and nbin in micpara.dat is different check!'
611  call prc_abort
612  endif
613 
614  ! grid parameter
615  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'Radius of cloud *'
616  do n = 1, nbin
617  read( fid_micpara,* ) nn, xctr( n ), radc( n )
618  log_info("ATMOS_PHY_MP_suzuki10_setup",'(A,1x,I3,1x,A,1x,ES15.7,1x,A)') &
619  "Radius of ", n, "th cloud bin (bin center)= ", radc( n ) , "[m]"
620  enddo
621  do n = 1, nbin+1
622  read( fid_micpara,* ) nn, xbnd( n )
623  enddo
624  read( fid_micpara,* ) dxmic
625  log_info("ATMOS_PHY_MP_suzuki10_setup",*) 'Width of Cloud SDF= ', dxmic
626 
627  ! capacity
628  do myu = 1, nspc_mk
629  do n = 1, nbin
630 ! read( fid_micpara,* ) mmyu, nn, cctr( myu,n )
631  read( fid_micpara,* ) mmyu, nn, cctr( n,myu )
632  enddo
633  do n = 1, nbin+1
634 ! read( fid_micpara,* ) mmyu, nn, cbnd( myu,n )
635  read( fid_micpara,* ) mmyu, nn, cbnd( n,myu )
636  enddo
637  enddo
638 
639  ! collection kernel
640  do myu = 1, nspc_mk
641  do nyu = 1, nspc_mk
642  do i = 1, nbin
643  do j = 1, nbin
644  read( fid_micpara,* ) mmyu, nnyu, mm, nn, ck( myu,nyu,i,j )
645  enddo
646  enddo
647  enddo
648  enddo
649 
650  ! terminal velocity
651  do myu = 1, nspc_mk
652  do n = 1, nbin
653  read( fid_micpara,* ) mmyu, nn, vt( myu,n )
654  enddo
655  enddo
656 
657  ! bulk density
658  do myu = 1, nspc_mk
659  do n = 1, nbin
660  read( fid_micpara,* ) mmyu, nn, br( myu,n )
661  enddo
662  enddo
663 
664  close ( fid_micpara )
665 
666  endif
667 
668  endif
669 
670  call comm_bcast( nbin, radc(:) )
671  call comm_bcast( nbin, xctr(:) )
672  call comm_bcast( dxmic )
673  call comm_bcast( nbin+1, xbnd(:) )
674  call comm_bcast( nbin, nspc_mk, cctr(:,:) )
675  call comm_bcast( nbin+1, nspc_mk, cbnd(:,:) )
676  call comm_bcast( nspc_mk, nspc_mk, nbin, nbin, ck(:,:,:,:) )
677  call comm_bcast( nspc_mk, nbin, br(:,:) )
678  call comm_bcast( nspc_mk, nbin, vt(:,:) )
679 
680  allocate( flg_noninduct( nspc,nspc ) )
681  allocate( ecoll( nspc,nspc,nbin,nbin ) )
682  allocate( rcoll( nspc,nspc,nbin,nbin ) )
683  !$omp workshare
684  flg_noninduct(:,:) = 0.0_rp
685  ecoll( :,:,:,: ) = 0.0_rp
686  rcoll( :,:,:,: ) = 0.0_rp
687  !$omp end workshare
688 
689  if ( present(flg_lt) ) then
690  flg_lt_ = flg_lt
691  else
692  flg_lt_ = .false.
693  end if
694  if( flg_lt_ ) then
695 
696  !$omp parallel do
697  do nyu = 1, nspc
698  do myu = 1, nspc
699  if( ( myu >= ic .and. myu <= iss ) .and. ( nyu == ig .or. nyu == ih ) ) then
700  flg_noninduct( myu,nyu ) = 1.0_rp
701  endif
702  enddo
703  enddo
704 
705  !$omp parallel do collapse(2)
706  do j = 1, nbin
707  do i = 1, nbin
708  do nyu = 1, nspc
709  do myu = 1, nspc
710  if( vt( myu,i ) /= vt( nyu,j ) ) then
711  ecoll( myu,nyu,i,j ) = ck( myu,nyu,i,j ) &
712  / ( pi*( radc( i )+radc( j ) )**2 * abs( vt( myu,i )-vt( nyu,j ) ) )
713  ecoll( myu,nyu,i,j ) = max( min( 1.0_rp, ecoll( myu,nyu,i,j ) ),0.0_rp )
714  else
715  ecoll( myu,nyu,i,j ) = 0.0_rp
716  endif
717 
718  if( ecoal_gsi /= 0.0_rp ) then
719  ecoll( myu,nyu,i,j ) = ecoal_gsi
720  endif
721 
722  if( ecoll( myu,nyu,i,j ) /= 0.0_rp ) then
723  rcoll( myu,nyu,i,j ) = ( 1.0_rp-ecoll( myu,nyu,i,j ) ) / ecoll( myu,nyu,i,j )
724  elseif( ecoll( myu,nyu,i,j ) == 0.0_rp ) then
725  rcoll( myu,nyu,i,j ) = 1.0_rp
726  endif
727  enddo
728  enddo
729  enddo
730  enddo
731 
732  endif
733 
734  !--- aerosol ( CCN ) (not supported)
735  if ( nccn /= 0 ) then
736 
737  xasta = log( rhoa*4.0_rp/3.0_rp*pi * ( rasta )**3 )
738  xaend = log( rhoa*4.0_rp/3.0_rp*pi * ( raend )**3 )
739 
740  dxaer = ( xaend-xasta )/nccn
741 
742  !$omp parallel do
743  do n = 1, nccn+1
744  xabnd( n ) = xasta + dxaer*( n-1 )
745  enddo
746  !$omp parallel do
747  do n = 1, nccn
748  xactr( n ) = ( xabnd( n )+xabnd( n+1 ) )*0.50_rp
749  rada( n ) = ( exp( xactr( n ) )*thirdovforth/pi/rhoa )**( oneovthird )
750  end do
751  do n = 1, nccn
752  log_info("ATMOS_PHY_MP_suzuki10_setup",'(A,1x,I3,1x,A,1x,ES15.7,1x,A)') &
753  "Radius of ", n, "th aerosol bin (bin center)= ", rada( n ) , "[m]"
754  enddo
755 
756  if ( flg_sf_aero ) then
757  log_error("ATMOS_PHY_MP_suzuki10_setup",*) "flg_sf_aero=true is not supported stop!! "
758  call prc_abort
759 ! if ( CZ(KS) >= 10.0_RP ) then
760 ! R10M1 = 10.0_RP / CZ(KS) * 0.50_RP ! scale with height
761 ! R10M2 = 10.0_RP / CZ(KS) * 0.50_RP ! scale with height
762 ! R10H1 = 1.0_RP * 0.50_RP
763 ! R10H2 = 1.0_RP * 0.0_RP
764 ! R10E1 = 1.0_RP * 0.50_RP
765 ! R10E2 = 1.0_RP * 0.50_RP
766 ! K10_1 = KS
767 ! K10_2 = KS
768 ! else
769 ! k = 1
770 ! do while ( CZ(k) < 10.0_RP )
771 ! k = k + 1
772 ! K10_1 = k
773 ! K10_2 = k + 1
774 ! R10M1 = ( CZ(k+1) - 10.0_RP ) / CDZ(k)
775 ! R10M2 = ( 10.0_RP - CZ(k) ) / CDZ(k)
776 ! R10H1 = ( CZ(k+1) - 10.0_RP ) / CDZ(k)
777 ! R10H2 = ( 10.0_RP - CZ(k) ) / CDZ(k)
778 ! R10E1 = ( CZ(k+1) - 10.0_RP ) / CDZ(k)
779 ! R10E2 = ( 10.0_RP - CZ(k) ) / CDZ(k)
780 ! enddo
781 ! endif
782  endif
783 
784  endif
785 
786  !--- determine nbnd
787  do n = 1, nbin
788  if( radc( n ) > rbnd ) then
789  nbnd = n
790  exit
791  endif
792  enddo
793  log_info("ATMOS_PHY_MP_suzuki10_setup",'(A,ES15.7,A)') 'Radius between cloud and rain is ', radc(nbnd), '[m]'
794  atmos_phy_mp_suzuki10_nbnd = nbnd
795 
796  !--- random number setup for stochastic method
797  if ( flg_rndm ) then
798  call random_setup( ia*ja*ka )
799  endif
800 
801  if ( mp_couple_aerosol .AND. nccn /=0 ) then
802  log_error("ATMOS_PHY_MP_suzuki10_setup",*) 'nccn should be 0 when MP_couple_aerosol = .true. !! stop'
803  call prc_abort
804  endif
805 
806  if ( nccn /= 0 ) then
807  !$omp parallel do
808  do n = 1, nccn
809  expxactr( n ) = exp( xactr( n ) )
810  rexpxactr( n ) = 1.0_rp / exp( xactr( n ) )
811  enddo
812  !$omp parallel do
813  do n = 1, nccn+1
814  expxabnd( n ) = exp( xabnd( n ) )
815  rexpxabnd( n ) = 1.0_rp / exp( xabnd( n ) )
816  enddo
817  endif
818 
819  allocate( vterm(qa-1) )
820  !$omp workshare
821  vterm(:) = 0.0_rp
822  !$omp end workshare
823  !$omp parallel do
824  do myu = 1, nspc
825  do n = 1, nbin
826  vterm((myu-1)*nbin+n) = -vt( myu,n )
827  enddo
828  enddo
829  !$omp parallel do
830  do n = 1, nbin
831  expxctr( n ) = exp( xctr( n ) )
832  rexpxctr( n ) = 1.0_rp / exp( xctr( n ) )
833  enddo
834  !$omp parallel do
835  do n = 1, nbin+1
836  expxbnd( n ) = exp( xbnd( n ) )
837  rexpxbnd( n ) = 1.0_rp / exp( xbnd( n ) )
838  enddo
839 
840  allocate( kindx(nbin,nbin) )
841  call getrule( ifrsl,kindx )
842 
843  !--- determine the parameters for interpolating SDF from qxx, Nxx of parent domain
844  sigma_sdf(1) = 0.2_rp
845  sigma_sdf(2) = 0.35_rp
846  sigma_sdf(3) = 0.35_rp
847  sigma_sdf(4) = 0.35_rp
848  sigma_sdf(5) = 0.35_rp
849  r0_sdf(1) = 5.e-6_rp
850  r0_sdf(2) = 2.61e-6_rp
851  r0_sdf(3) = 5.e-6_rp
852  r0_sdf(4) = 2.61e-6_rp
853  r0_sdf(5) = 2.61e-6_rp ! to be corrected
854  n0_sdf(1) = 8.0e+6_rp
855  n0_sdf(2) = 0.0_rp
856  n0_sdf(3) = 3.0e+6_rp
857  n0_sdf(4) = 4.0e+6_rp
858  n0_sdf(5) = 4.0e+6_rp ! to be corrected
859  rho_sdf(1) = dwatr
860  rho_sdf(2) = dice
861  rho_sdf(3) = 100.0_rp
862  rho_sdf(4) = 400.0_rp
863  rho_sdf(5) = 400.0_rp ! to be corrected
864 
865  !--- determine the parameters for interpolating SDF from qxx, Nxx of parent domain
866  sigma_sdf(1) = 0.2_rp
867  sigma_sdf(2) = 0.35_rp
868  sigma_sdf(3) = 0.35_rp
869  sigma_sdf(4) = 0.35_rp
870  sigma_sdf(5) = 0.35_rp
871  r0_sdf(1) = 5.e-6_rp
872  r0_sdf(2) = 2.61e-6_rp
873  r0_sdf(3) = 5.e-6_rp
874  r0_sdf(4) = 2.61e-6_rp
875  r0_sdf(5) = 2.61e-6_rp ! to be corrected
876  n0_sdf(1) = 8.0e+6_rp
877  n0_sdf(2) = 0.0_rp
878  n0_sdf(3) = 3.0e+6_rp
879  n0_sdf(4) = 4.0e+6_rp
880  n0_sdf(5) = 4.0e+6_rp ! to be corrected
881  rho_sdf(1) = dwatr
882  rho_sdf(2) = dice
883  rho_sdf(3) = 100.0_rp
884  rho_sdf(4) = 400.0_rp
885  rho_sdf(5) = 400.0_rp ! to be corrected
886 
887  !$acc update device(vterm)
888 
889  return

References atmos_phy_mp_suzuki10_nbnd, scale_const::const_dice, scale_const::const_dwatr, scale_const::const_pi, scale_atmos_hydrometeor::i_hc, scale_atmos_hydrometeor::i_hg, scale_atmos_hydrometeor::i_hh, scale_atmos_hydrometeor::i_hi, scale_atmos_hydrometeor::i_hr, scale_atmos_hydrometeor::i_hs, scale_io::io_fid_conf, scale_io::io_get_available_fid(), nbin, nccn, scale_prc::prc_abort(), scale_prc::prc_ismaster, and scale_prc::prc_masterrank.

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_setup().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_finalize()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_finalize

finalize

Definition at line 895 of file scale_atmos_phy_mp_suzuki10.F90.

895 
896  deallocate( atmos_phy_mp_suzuki10_tracer_names )
897  deallocate( atmos_phy_mp_suzuki10_tracer_descriptions )
898  deallocate( atmos_phy_mp_suzuki10_tracer_units )
899 
900  deallocate( xctr )
901  deallocate( xbnd )
902  deallocate( radc )
903  deallocate( cctr )
904  deallocate( cbnd )
905  deallocate( ck )
906  deallocate( vt )
907  deallocate( br )
908  deallocate( ifrsl )
909  deallocate( expxctr )
910  deallocate( expxbnd )
911  deallocate( rexpxctr )
912  deallocate( rexpxbnd )
913  if ( nccn /= 0 ) then
914  deallocate( xactr )
915  deallocate( xabnd )
916  deallocate( rada )
917  deallocate( expxactr )
918  deallocate( expxabnd )
919  deallocate( rexpxactr )
920  deallocate( rexpxabnd )
921  endif
922 
923  deallocate( flg_noninduct )
924  deallocate( ecoll )
925  deallocate( rcoll )
926 
927  deallocate( vterm )
928 
929  deallocate( kindx )
930 
931 
932  return

References atmos_phy_mp_suzuki10_tracer_descriptions, atmos_phy_mp_suzuki10_tracer_names, atmos_phy_mp_suzuki10_tracer_units, and nccn.

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_finalize().

Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_tendency()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_tendency ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
integer, intent(in)  KIJMAX,
real(dp), intent(in)  dt,
real(rp), dimension (ka,ia,ja), intent(in)  DENS,
real(rp), dimension (ka,ia,ja), intent(in)  PRES,
real(rp), dimension (ka,ia,ja), intent(in)  TEMP,
real(rp), dimension (ka,ia,ja,qa), intent(in)  QTRC,
real(rp), dimension (ka,ia,ja), intent(in)  QDRY,
real(rp), dimension(ka,ia,ja), intent(in)  CPtot,
real(rp), dimension(ka,ia,ja), intent(in)  CVtot,
real(rp), dimension (ka,ia,ja), intent(in)  CCN,
real(rp), dimension (ka,ia,ja,qa), intent(out)  RHOQ_t,
real(rp), dimension (ka,ia,ja), intent(out)  RHOE_t,
real(rp), dimension(ka,ia,ja), intent(out)  CPtot_t,
real(rp), dimension(ka,ia,ja), intent(out)  CVtot_t,
real(rp), dimension(ka,ia,ja), intent(out)  EVAPORATE,
logical, intent(in), optional  flg_lt,
real(rp), intent(in), optional  d0_crg,
real(rp), intent(in), optional  v0_crg,
real(rp), dimension(ka,ia,ja), intent(in), optional  dqcrg,
real(rp), dimension(ka,ia,ja), intent(in), optional  beta_crg,
real(rp), dimension(ka,ia,ja,num_hyd), intent(in), optional  QTRC_crg,
real(rp), dimension(ka,ia,ja,3), intent(out), optional  QSPLT_in,
real(rp), dimension(ka,ia,ja,num_hyd), intent(out), optional  Sarea,
real(rp), dimension(ka,ia,ja,num_hyd), intent(out), optional  RHOC_t_mp 
)

Cloud Microphysics.

Definition at line 954 of file scale_atmos_phy_mp_suzuki10.F90.

954  use scale_const, only: &
955  tem00 => const_tem00, &
956  pi => const_pi
957  use scale_atmos_saturation, only: &
958  atmos_saturation_pres2qsat_liq, &
959  atmos_saturation_pres2qsat_ice
960  implicit none
961 
962  integer, intent(in) :: KA, KS, KE
963  integer, intent(in) :: IA, IS, IE
964  integer, intent(in) :: JA, JS, JE
965  integer, intent(in) :: KIJMAX
966 
967  real(DP), intent(in) :: dt
968  real(RP), intent(in) :: DENS (KA,IA,JA)
969  real(RP), intent(in) :: PRES (KA,IA,JA)
970  real(RP), intent(in) :: TEMP (KA,IA,JA)
971  real(RP), intent(in) :: QTRC (KA,IA,JA,QA)
972  real(RP), intent(in) :: QDRY (KA,IA,JA)
973  real(RP), intent(in) :: CPtot(KA,IA,JA)
974  real(RP), intent(in) :: CVtot(KA,IA,JA)
975  real(RP), intent(in) :: CCN (KA,IA,JA)
976 
977  real(RP), intent(out) :: RHOQ_t (KA,IA,JA,QA)
978  real(RP), intent(out) :: RHOE_t (KA,IA,JA)
979  real(RP), intent(out) :: CPtot_t(KA,IA,JA)
980  real(RP), intent(out) :: CVtot_t(KA,IA,JA)
981  real(RP), intent(out) :: EVAPORATE(KA,IA,JA) !--- number of evaporated cloud [/m3]
982 
983  ! Optional for Lightning
984  logical, intent(in), optional :: flg_lt
985  real(RP), intent(in), optional :: d0_crg, v0_crg
986  real(RP), intent(in), optional :: dqcrg(KA,IA,JA)
987  real(RP), intent(in), optional :: beta_crg(KA,IA,JA)
988  real(RP), intent(in), optional :: QTRC_crg(KA,IA,JA,num_hyd)
989  real(RP), intent(out), optional :: QSPLT_in(KA,IA,JA,3)
990  real(RP), intent(out), optional :: Sarea(KA,IA,JA,num_hyd)
991  real(RP), intent(out), optional :: RHOC_t_mp(KA,IA,JA,num_hyd)
992 
993  real(RP) :: QSAT_L(KA,IA,JA)
994  real(RP) :: QSAT_I(KA,IA,JA)
995  real(RP) :: ssliq(KA,IA,JA)
996  real(RP) :: ssice(KA,IA,JA)
997 
998  integer :: ijk_index (KIJMAX,3)
999  integer :: index_cld (KIJMAX)
1000  integer :: index_cold(KIJMAX)
1001  integer :: index_warm(KIJMAX)
1002  integer :: ijkcount, ijkcount_cold, ijkcount_warm
1003  integer :: ijk, indirect
1004 
1005  real(RP) :: DENS_ijk(KIJMAX)
1006  real(RP) :: PRES_ijk(KIJMAX)
1007  real(RP) :: TEMP_ijk(KIJMAX)
1008  real(RP) :: Qdry_ijk(KIJMAX)
1009  real(RP) :: Qvap_ijk(KIJMAX)
1010  real(RP) :: CCN_ijk(KIJMAX)
1011  real(RP) :: CP_ijk(KIJMAX)
1012  real(RP) :: CV_ijk(KIJMAX)
1013  real(RP) :: Evaporate_ijk(KIJMAX)
1014  real(RP) :: Ghyd_ijk(nbin,nspc,KIJMAX)
1015  real(RP) :: Gaer_ijk(max(nccn,1),KIJMAX)
1016  real(RP) :: cldsum
1017  integer :: countbin
1018  real(RP) :: rhoq_new
1019 
1020  !--- for lithgning
1021  logical :: flg_lt_l
1022  real(RP) :: d0_crg_l, v0_crg_l
1023  real(RP) :: Gcrg_ijk(nbin,nspc,KIJMAX)
1024  real(RP) :: CRG_SEP_ijk(nspc,KIJMAX)
1025  real(RP) :: dqcrg_ijk(KIJMAX)
1026  real(RP) :: beta_crg_ijk(KIJMAX)
1027 
1028  integer :: step
1029  integer :: k, i, j, m, n, iq
1030  !---------------------------------------------------------------------------
1031 
1032  if ( nspc == 1 ) then
1033  log_progress(*) 'atmosphere / physics / microphysics / SBM (Liquid water only)'
1034  elseif( nspc > 1 ) then
1035  log_progress(*) 'atmosphere / physics / microphysics / SBM (Mixed phase)'
1036  endif
1037 
1038  flg_lt_l = .false.
1039  if ( present(flg_lt) ) then
1040  flg_lt_l = flg_lt
1041  end if
1042 
1043  if ( flg_lt_l ) then
1044  !$omp workshare
1045  crg_sep_ijk(:,:) = 0.0_rp
1046  gcrg_ijk(:,:,:) = 0.0_rp
1047  qsplt_in(:,:,:,:) = 0.0_rp
1048  !$omp end workshare
1049  d0_crg_l = d0_crg
1050  v0_crg_l = v0_crg
1051  end if
1052 
1053  call atmos_saturation_pres2qsat_liq( ka, ks, ke, & ! [IN]
1054  ia, is, ie, & ! [IN]
1055  ja, js, je, & ! [IN]
1056  temp(:,:,:), pres(:,:,:), qdry(:,:,:), & ! [IN]
1057  qsat_l(:,:,:) ) ! [OUT]
1058 
1059  call atmos_saturation_pres2qsat_ice( ka, ks, ke, & ! [IN]
1060  ia, is, ie, & ! [IN]
1061  ja, js, je, & ! [IN]
1062  temp(:,:,:), pres(:,:,:), qdry(:,:,:), & ! [IN]
1063  qsat_i(:,:,:) ) ! [OUT]
1064 
1065  !$omp parallel do
1066  do j = js, je
1067  do i = is, ie
1068  do k = ks, ke
1069  ssliq(k,i,j) = qtrc(k,i,j,i_qv) / qsat_l(k,i,j) - 1.0_rp
1070  ssice(k,i,j) = qtrc(k,i,j,i_qv) / qsat_i(k,i,j) - 1.0_rp
1071  enddo
1072  enddo
1073  enddo
1074 
1075  if ( nspc == 1 ) then
1076  !$omp workshare
1077  ssice(:,:,:) = 0.0_rp
1078  !$omp end workshare
1079  endif
1080 
1081 !--- store initial SDF of aerosol
1082 !--- this option is not supported
1083 ! if ( ofirst_sdfa ) then
1084 ! allocate( marate( nccn ) )
1085 ! do j = JS, JE
1086 ! do i = IS, IE
1087 ! do k = KS, KE
1088 ! sum2 = 0.0_RP
1089 ! do n = 1, nccn
1090 ! marate( n ) = gdga(k,i,j,n)*rexpxactr( n )
1091 ! sum2 = sum2 + gdga(k,i,j,n)*rexpxactr( n )
1092 ! enddo
1093 ! enddo
1094 ! enddo
1095 ! enddo
1096 ! if ( sum2 /= 0.0_RP ) then
1097 ! marate( 1:nccn ) = marate( 1:nccn )/sum2
1098 ! ofirst_sdfa = .false.
1099 ! endif
1100 ! endif
1101 
1102  !--- Arrange array for microphysics
1103 
1104  call prof_rapstart('MP_ijkconvert', 3)
1105 
1106  !$omp parallel do private(ijk)
1107  do j = js, je
1108  do i = is, ie
1109  do k = ks, ke
1110  ijk = 1 + (k-ks) + (ke-ks+1) * ( (i-is) + (ie-is+1) * (j-js) )
1111  ijk_index(ijk,1) = i
1112  ijk_index(ijk,2) = j
1113  ijk_index(ijk,3) = k
1114  end do
1115  end do
1116  end do
1117 
1118  ijkcount = 0
1119  do j = js, je
1120  do i = is, ie
1121  do k = ks, ke
1122  ! calc total hydrometeors
1123  cldsum = 0.0_rp
1124  countbin = i_qv + 1
1125  do m = 1, nspc
1126  do n = 1, nbin
1127  cldsum = cldsum + qtrc(k,i,j,countbin) * dens(k,i,j) / dxmic
1128  countbin = countbin + 1
1129  enddo
1130  enddo
1131 
1132  if ( cldsum > cldmin &
1133  .OR. ssliq(k,i,j) > 0.0_rp &
1134  .OR. ssice(k,i,j) > 0.0_rp ) then
1135  ijkcount = ijkcount + 1
1136  ijk = 1 + (k-ks) + (ke-ks+1) * ( (i-is) + (ie-is+1) * (j-js) )
1137  index_cld(ijkcount) = ijk
1138 
1139  else
1140 
1141  ! no hudrometeors and undersaturation (no microphysical process occcurs)
1142  do iq = 1, qa
1143  rhoq_t(k,i,j,iq) = 0.0_rp
1144  end do
1145  rhoe_t(k,i,j) = 0.0_rp
1146  cptot_t(k,i,j) = 0.0_rp
1147  cvtot_t(k,i,j) = 0.0_rp
1148  evaporate(k,i,j) = 0.0_rp
1149 
1150  end if
1151 
1152  end do
1153  end do
1154  end do
1155 
1156  !$omp parallel do private(indirect,i,j,k,countbin)
1157  do ijk = 1, ijkcount
1158  indirect = index_cld(ijk)
1159  i = ijk_index(indirect,1)
1160  j = ijk_index(indirect,2)
1161  k = ijk_index(indirect,3)
1162 
1163  dens_ijk(ijk) = dens(k,i,j)
1164  pres_ijk(ijk) = pres(k,i,j)
1165  temp_ijk(ijk) = temp(k,i,j)
1166  qdry_ijk(ijk) = qdry(k,i,j)
1167  cp_ijk(ijk) = cptot(k,i,j)
1168  cv_ijk(ijk) = cvtot(k,i,j)
1169  ccn_ijk(ijk) = ccn(k,i,j)
1170  qvap_ijk(ijk) = qtrc(k,i,j,i_qv)
1171 
1172  countbin = i_qv + 1
1173  do m = 1, nspc
1174  do n = 1, nbin
1175  ghyd_ijk(n,m,ijk) = qtrc(k,i,j,countbin) * dens(k,i,j) / dxmic
1176  countbin = countbin + 1
1177  enddo
1178  enddo
1179 
1180  do n = 1, nccn
1181  gaer_ijk(n,ijk) = qtrc(k,i,j,countbin) * dens(k,i,j) / dxaer
1182  countbin = countbin + 1
1183  enddo
1184 
1185  end do
1186 
1187  ijkcount_cold = 0
1188  ijkcount_warm = 0
1189  if ( nspc > 1 ) then
1190  do ijk = 1, ijkcount
1191  if ( temp_ijk(ijk) < tem00 ) then ! cold
1192  ijkcount_cold = ijkcount_cold + 1
1193  index_cold(ijkcount_cold) = ijk
1194  else ! warm
1195  ijkcount_warm = ijkcount_warm + 1
1196  index_warm(ijkcount_warm) = ijk
1197  endif
1198  end do
1199  else ! warn
1200  !$omp parallel do
1201  do ijk = 1, ijkcount
1202  index_warm(ijk) = ijk
1203  end do
1204  ijkcount_warm = ijkcount
1205  end if
1206 
1207  if ( flg_lt_l ) then
1208  !$omp parallel do private(indirect,i,j,k,countbin)
1209  do ijk = 1, ijkcount
1210  indirect = index_cld(ijk)
1211  i = ijk_index(indirect,1)
1212  j = ijk_index(indirect,2)
1213  k = ijk_index(indirect,3)
1214 
1215  countbin = 1
1216  do m = 1, nspc
1217  do n = 1, nbin
1218  gcrg_ijk(n,m,ijk) = qtrc_crg(k,i,j,countbin) * dens(k,i,j)
1219  countbin = countbin + 1
1220  enddo
1221  enddo
1222  beta_crg_ijk(ijk) = beta_crg(k,i,j)
1223  dqcrg_ijk(ijk) = dqcrg(k,i,j)
1224  end do
1225  end if
1226 
1227  call prof_rapend ('MP_ijkconvert', 3)
1228 
1229  ! tentative timername registration
1230  call prof_rapstart('MP_suzuki10', 3)
1231  call prof_rapend ('MP_suzuki10', 3)
1232  call prof_rapstart('_SBM_Nucleat', 3)
1233  call prof_rapend ('_SBM_Nucleat', 3)
1234 ! call PROF_rapstart('_SBM_NucleatA', 3)
1235 ! call PROF_rapend ('_SBM_NucleatA', 3)
1236  call prof_rapstart('_SBM_Liqphase', 3)
1237  call prof_rapend ('_SBM_Liqphase', 3)
1238  call prof_rapstart('_SBM_Icephase', 3)
1239  call prof_rapend ('_SBM_Icephase', 3)
1240  call prof_rapstart('_SBM_Mixphase', 3)
1241  call prof_rapend ('_SBM_Mixphase', 3)
1242  call prof_rapstart('_SBM_AdvLiq', 3)
1243  call prof_rapend ('_SBM_AdvLiq', 3)
1244  call prof_rapstart('_SBM_AdvIce', 3)
1245  call prof_rapend ('_SBM_AdvIce', 3)
1246  call prof_rapstart('_SBM_AdvMix', 3)
1247  call prof_rapend ('_SBM_AdvMix', 3)
1248 ! call PROF_rapstart('_SBM_FAero', 3)
1249 ! call PROF_rapend ('_SBM_FAero', 3)
1250  call prof_rapstart('_SBM_Freezing', 3)
1251  call prof_rapend ('_SBM_Freezing', 3)
1252  call prof_rapstart('_SBM_IceNucleat', 3)
1253  call prof_rapend ('_SBM_IceNucleat', 3)
1254  call prof_rapstart('_SBM_Melting', 3)
1255  call prof_rapend ('_SBM_Melting', 3)
1256  call prof_rapstart('_SBM_CollCoag', 3)
1257  call prof_rapend ('_SBM_CollCoag', 3)
1258 ! call PROF_rapstart('_SBM_CollCoagR', 3)
1259 ! call PROF_rapend ('_SBM_CollCoagR', 3)
1260 
1261  if ( ijkcount > 0 ) then
1262 
1263  call prof_rapstart('MP_suzuki10', 3)
1264 
1265  call mp_suzuki10( ka, ia, ja, & ! [IN]
1266  ijkcount, & ! [IN]
1267  ijkcount_cold, & ! [IN]
1268  ijkcount_warm, & ! [IN]
1269  index_cold( 1:ijkcount), & ! [IN]
1270  index_warm( 1:ijkcount), & ! [IN]
1271  dens_ijk( 1:ijkcount), & ! [IN]
1272  pres_ijk( 1:ijkcount), & ! [IN]
1273  qdry_ijk( 1:ijkcount), & ! [IN]
1274  ccn_ijk( 1:ijkcount), & ! [IN]
1275  temp_ijk( 1:ijkcount), & ! [INOUT]
1276  qvap_ijk( 1:ijkcount), & ! [INOUT]
1277  ghyd_ijk(:,:,1:ijkcount), & ! [INOUT]
1278  gaer_ijk(:, 1:ijkcount), & ! [INOUT]
1279  cp_ijk( 1:ijkcount), & ! [INOUT]
1280  cv_ijk( 1:ijkcount), & ! [INOUT]
1281  evaporate_ijk(1:ijkcount), & ! [OUT]
1282  dt, & ! [IN]
1283  flg_lt_l, & ! [IN]
1284  d0_crg_l, v0_crg_l, & ! [IN]
1285  dqcrg_ijk( 1:ijkcount), & ! [IN]
1286  beta_crg_ijk( 1:ijkcount), & ! [IN]
1287  gcrg_ijk(:,:,1:ijkcount), & ! [INOUT]
1288  crg_sep_ijk(:,1:ijkcount) ) ! [OUT]
1289 
1290  call prof_rapend ('MP_suzuki10', 3)
1291 
1292 ! if ( flg_sf_aero ) then
1293 ! do j = JS-2, JE+2
1294 ! do i = IS-2, IE+1
1295 ! VELX(i,j) = MOMX(K10_1,i,j) / ( DENS(K10_1,i+1,j)+DENS(K10_1,i,j) ) * R10M1 &
1296 ! + MOMX(K10_2,i,j) / ( DENS(K10_2,i+1,j)+DENS(K10_2,i,j) ) * R10M2
1297 ! enddo
1298 ! enddo
1299 !
1300 ! do j = JS-2, JE+1
1301 ! do i = IS-2, IE+2
1302 ! VELY(i,j) = MOMY(K10_1,i,j) / ( DENS(K10_1,i,j+1)+DENS(K10_1,i,j) ) * R10M1 &
1303 ! + MOMY(K10_2,i,j) / ( DENS(K10_2,i,j+1)+DENS(K10_2,i,j) ) * R10M2
1304 ! enddo
1305 ! enddo
1306 ! endif
1307 !
1308 ! !--- SURFACE FLUX by Monahan et al. (1986)
1309 ! if ( flg_sf_aero .AND. nccn /= 0 ) then
1310 ! do j = JS, JE
1311 ! do i = IS, IE
1312 ! ijk = ( j - JS ) * KMAX * IMAX &
1313 ! + ( i - IS ) * KMAX &
1314 ! + ( KS - KS ) &
1315 ! + 1
1316 ! Uabs = sqrt( ( ( VELX(i,j) + VELX(i-1,j ) ) * 0.50_RP )**2 &
1317 ! + ( ( VELY(i,j) + VELY(i ,j-1) ) * 0.50_RP )**2 )
1318 ! do n = 1, nccn
1319 ! if ( rada( n ) <= 2.0E-5_RP .AND. rada( n ) >= 3.0E-7_RP ) then
1320 ! bparam = ( 0.38_RP - log( rada( n ) ) )/0.65_RP
1321 ! SFLX_AERO(i,j,n) = 1.373_RP * Uabs**( 3.41_RP ) * rada( n )**( -3.0_RP ) &
1322 ! * ( 1.0_RP + 0.057_RP * rada( n )**( 1.05_RP ) ) &
1323 ! * 10.0_RP**( 1.19_RP * exp( -bparam*bparam ) )
1324 ! ! convert from [#/m^2/um/s] -> [kg/m^3/unit log (m)]
1325 ! SFLX_AERO(i,j,n) = SFLX_AERO(i,j,n) / DENS(KS,i,j) &
1326 ! / CDZ(KS) * rada( n ) / 3.0_RP * dt * expxactr( n )
1327 ! Gaer_ijk(n,ijk) = Gaer_ijk(n,ijk) + SFLX_AERO(i,j,n)/dxaer
1328 ! endif
1329 ! enddo
1330 ! enddo
1331 ! enddo
1332 ! endif
1333 
1334  call prof_rapstart('MP_ijkconvert', 3)
1335 
1336  !---- return original array
1337  !$omp parallel do private(indirect,i,j,k,countbin,rhoq_new)
1338  do ijk = 1, ijkcount
1339  indirect = index_cld(ijk)
1340  i = ijk_index(indirect,1)
1341  j = ijk_index(indirect,2)
1342  k = ijk_index(indirect,3)
1343 
1344  rhoe_t(k,i,j) = ( temp_ijk(ijk) * cv_ijk(ijk) - temp(k,i,j) * cvtot(k,i,j) ) * dens(k,i,j) / dt
1345  cptot_t(k,i,j) = ( cp_ijk(ijk) - cptot(k,i,j) ) / dt
1346  cvtot_t(k,i,j) = ( cv_ijk(ijk) - cvtot(k,i,j) ) / dt
1347  evaporate(k,i,j) = evaporate_ijk(ijk) / dt ! [#/m3/s]
1348 
1349  rhoq_t(k,i,j,i_qv) = ( qvap_ijk(ijk) - qtrc(k,i,j,i_qv) ) * dens(k,i,j) / dt
1350 
1351  countbin = i_qv + 1
1352  do m = 1, nspc
1353  do n = 1, nbin
1354  rhoq_new = ghyd_ijk(n,m,ijk) * dxmic
1355  rhoq_t(k,i,j,countbin) = ( rhoq_new - qtrc(k,i,j,countbin)*dens(k,i,j) ) / dt
1356  countbin = countbin + 1
1357  enddo
1358  enddo
1359 
1360  do n = 1, nccn
1361  rhoq_new = gaer_ijk(n,ijk) * dxaer
1362  rhoq_t(k,i,j,countbin) = ( rhoq_new - qtrc(k,i,j,countbin)*dens(k,i,j) ) / dt
1363  countbin = countbin + 1
1364  enddo
1365 
1366  if( flg_lt_l ) then
1367  countbin = 1
1368  do m = 1, nspc
1369  do n = 1, nbin
1370  rhoq_new = gcrg_ijk(n,m,ijk)
1371  rhoc_t_mp(k,i,j,countbin) = ( rhoq_new - qtrc_crg(k,i,j,countbin)*dens(k,i,j) ) / dt
1372  countbin = countbin + 1
1373  enddo
1374  enddo
1375 
1376  sarea(k,i,j,:) = 0.0_rp
1377  countbin = 1
1378  do m = 1, nspc
1379  do n = 1, nbin
1380  rhoq_new = ghyd_ijk(n,m,ijk) * dxmic
1381  sarea(k,i,j,countbin) = 4.0_rp*pi*radc(n)**2*rhoq_new*rexpxctr( n )
1382  countbin = countbin + 1
1383  enddo
1384  enddo
1385 
1386  qsplt_in(k,i,j,1) = crg_sep_ijk(ig,ijk) * dens(k,i,j) / dt
1387  qsplt_in(k,i,j,2) = ( crg_sep_ijk(ic,ijk) &
1388  + crg_sep_ijk(ip,ijk) &
1389  + crg_sep_ijk(id,ijk) ) * dens(k,i,j) / dt
1390  qsplt_in(k,i,j,3) = crg_sep_ijk(iss,ijk) * dens(k,i,j) / dt
1391 
1392  endif
1393 
1394  enddo
1395 
1396 
1397 ! if ( nccn /= 0 ) then
1398 ! AMR(:,:,:) = 0.0_RP
1399 ! do j = JS, JE
1400 ! do i = IS, IE
1401 ! do k = KS, KE
1402 ! do n = 1, nccn
1403 ! AMR(k,i,j) = AMR(k,i,j) + QTRC(k,i,j,QQE-1+n)
1404 ! enddo
1405 ! enddo
1406 ! enddo
1407 ! enddo
1408 ! endif
1409 
1410  call prof_rapend ('MP_ijkconvert', 3)
1411 
1412  endif
1413 
1414  return

References scale_const::const_pi, scale_const::const_tem00, nbin, nccn, scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_calc_tendency().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_terminal_velocity()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_terminal_velocity ( integer, intent(in)  KA,
real(rp), dimension(ka,qa-1), intent(out)  vterm_o 
)

get terminal velocity

Definition at line 1423 of file scale_atmos_phy_mp_suzuki10.F90.

1423  !$acc routine vector
1424  implicit none
1425 
1426  integer, intent(in) :: KA
1427 
1428  real(RP), intent(out) :: vterm_o(KA,QA-1)
1429 
1430  integer :: iq
1431  !---------------------------------------------------------------------------
1432 
1433  do iq = 1, qa-1
1434  vterm_o(:,iq) = vterm(iq)
1435  end do
1436 
1437  return

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_calc_tendency().

Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_cloud_fraction()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_cloud_fraction ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(rp), dimension (ka,ia,ja,num_hyd), intent(in)  QTRC0,
real(rp), intent(in)  mask_criterion,
real(rp), dimension(ka,ia,ja), intent(out)  cldfrac 
)

Calculate Cloud Fraction.

Definition at line 1449 of file scale_atmos_phy_mp_suzuki10.F90.

1449  implicit none
1450 
1451  integer, intent(in) :: KA, KS, KE
1452  integer, intent(in) :: IA, IS, IE
1453  integer, intent(in) :: JA, JS, JE
1454 
1455  real(RP), intent(in) :: QTRC0 (KA,IA,JA,num_hyd)
1456  real(RP), intent(in) :: mask_criterion
1457  real(RP), intent(out) :: cldfrac(KA,IA,JA)
1458 
1459  real(RP) :: qhydro
1460  integer :: k, i, j, iq, ihydro
1461  !---------------------------------------------------------------------------
1462 
1463  if( nspc > 1 ) then
1464  !$omp parallel do private(qhydro)
1465  do j = js, je
1466  do i = is, ie
1467  do k = ks, ke
1468  qhydro = 0.0_rp
1469  do ihydro = 1, nspc
1470  do iq = nbin*(ihydro-1)+1, nbin*ihydro
1471  qhydro = qhydro + qtrc0(k,i,j,iq)
1472  enddo
1473  enddo
1474  cldfrac(k,i,j) = 0.5_rp + sign(0.5_rp,qhydro-mask_criterion)
1475  enddo
1476  enddo
1477  enddo
1478  elseif( nspc == 1 ) then
1479  !$omp parallel do private(qhydro)
1480  do j = js, je
1481  do i = is, ie
1482  do k = ks, ke
1483  qhydro = 0.0_rp
1484  do ihydro = 1, i_mp_qc
1485  do iq = nbin*(ihydro-1)+1, nbin*ihydro
1486  qhydro = qhydro + qtrc0(k,i,j,iq)
1487  enddo
1488  enddo
1489  cldfrac(k,i,j) = 0.5_rp + sign(0.5_rp,qhydro-mask_criterion)
1490  enddo
1491  enddo
1492  enddo
1493  endif
1494 
1495  return

References nbin.

Referenced by mod_atmos_phy_mp_vars::atmos_phy_mp_vars_get_diagnostic().

Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_effective_radius()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_effective_radius ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(rp), dimension(ka,ia,ja), intent(in)  DENS0,
real(rp), dimension(ka,ia,ja), intent(in)  TEMP0,
real(rp), dimension(ka,ia,ja,num_hyd), intent(in)  QTRC0,
real(rp), dimension (ka,ia,ja,n_hyd), intent(out)  Re 
)

Calculate Effective Radius.

Definition at line 1508 of file scale_atmos_phy_mp_suzuki10.F90.

1508  use scale_const, only: &
1509  eps => const_eps
1510  use scale_atmos_hydrometeor, only: &
1511  n_hyd, &
1512  i_qv, &
1513  i_hc, &
1514  i_hr, &
1515  i_hi, &
1516  i_hs, &
1517  i_hg, &
1518  i_hh
1519  implicit none
1520 
1521  integer, intent(in) :: KA, KS, KE
1522  integer, intent(in) :: IA, IS, IE
1523  integer, intent(in) :: JA, JS, JE
1524 
1525  real(RP), intent(in) :: DENS0(KA,IA,JA) ! density [kg/m3]
1526  real(RP), intent(in) :: TEMP0(KA,IA,JA) ! temperature [K]
1527  real(RP), intent(in) :: QTRC0(KA,IA,JA,num_hyd) ! tracer mass concentration [kg/kg]
1528  real(RP), intent(out) :: Re (KA,IA,JA,N_HYD) ! effective radius [cm]
1529 
1530  real(RP), parameter :: um2cm = 100.0_rp
1531 
1532  real(RP) :: sum0(nspc), sum2, sum3, re_tmp(nspc)
1533  integer :: i, j, k, iq, ihydro
1534  !---------------------------------------------------------------------------
1535 
1536  !$omp parallel do private(sum2,sum3,ihydro)
1537  do k = ks, ke
1538  do j = js, je
1539  do i = is, ie
1540  re(k,i,j,:) = 0.0_rp
1541 
1542  ! HC
1543  sum3 = 0.0_rp
1544  sum2 = 0.0_rp
1545  ihydro = i_mp_qc
1546  do iq = 1, nbnd
1547  sum3 = sum3 &
1548  + ( ( qtrc0(k,i,j,iq) * dens0(k,i,j) ) & !--- [kg/kg] -> [kg/m3]
1549  * rexpxctr( iq-nbin*(ihydro-1) ) & !--- mass -> number
1550  * radc( iq-nbin*(ihydro-1) )**3.0_rp )
1551  sum2 = sum2 &
1552  + ( ( qtrc0(k,i,j,iq) * dens0(k,i,j) ) & !--- [kg/kg] -> [kg/m3]
1553  * rexpxctr( iq-nbin*(ihydro-1) ) & !--- mass -> number
1554  * radc( iq-nbin*(ihydro-1) )**2.0_rp )
1555  enddo
1556  sum3 = max( sum3, 0.0_rp )
1557  sum2 = max( sum2, 0.0_rp )
1558  if ( sum2 /= 0.0_rp ) then
1559  re(k,i,j,i_hc) = sum3 / sum2 * um2cm
1560  else
1561  re(k,i,j,i_hc) = 0.0_rp
1562  endif
1563 
1564  ! HR
1565  sum3 = 0.0_rp
1566  sum2 = 0.0_rp
1567  ihydro = i_mp_qc
1568  do iq = nbnd+1, nbin
1569  sum3 = sum3 &
1570  + ( ( qtrc0(k,i,j,iq) * dens0(k,i,j) ) & !--- [kg/kg] -> [kg/m3]
1571  * rexpxctr( iq-nbin*(ihydro-1) ) & !--- mass -> number
1572  * radc( iq-nbin*(ihydro-1) )**3.0_rp )
1573  sum2 = sum2 &
1574  + ( ( qtrc0(k,i,j,iq) * dens0(k,i,j) ) & !--- [kg/kg] -> [kg/m3]
1575  * rexpxctr( iq-nbin*(ihydro-1) ) & !--- mass -> number
1576  * radc( iq-nbin*(ihydro-1) )**2.0_rp )
1577  enddo
1578  sum3 = max( sum3, 0.0_rp )
1579  sum2 = max( sum2, 0.0_rp )
1580  if ( sum2 /= 0.0_rp ) then
1581  re(k,i,j,i_hr) = sum3 / sum2 * um2cm
1582  else
1583  re(k,i,j,i_hr) = 0.0_rp
1584  endif
1585 
1586  enddo
1587  enddo
1588  enddo
1589 
1590  ! other hydrometeors
1591  if ( nspc > 1 ) then
1592  !$omp parallel do private(sum0,sum2,sum3,re_tmp)
1593  do k = ks, ke
1594  do j = js, je
1595  do i = is, ie
1596  do ihydro = 2, nspc
1597  sum0(ihydro) = 0.0_rp
1598  sum2 = 0.0_rp
1599  sum3 = 0.0_rp
1600  do iq = nbin*(ihydro-1)+1, nbin*ihydro
1601  sum0(ihydro) = sum0(ihydro) &
1602  + ( qtrc0(k,i,j,iq) * dens0(k,i,j) ) !--- [kg/kg] -> [kg/m3]
1603  sum3 = sum3 &
1604  + ( ( qtrc0(k,i,j,iq) * dens0(k,i,j) ) & !--- [kg/kg] -> [kg/m3]
1605  * rexpxctr( iq-nbin*(ihydro-1) ) & !--- mass -> number
1606  * radc( iq-nbin*(ihydro-1) )**3.0_rp )
1607  sum2 = sum2 &
1608  + ( ( qtrc0(k,i,j,iq) * dens0(k,i,j) ) & !--- [kg/kg] -> [kg/m3]
1609  * rexpxctr( iq-nbin*(ihydro-1) ) & !--- mass -> number
1610  * radc( iq-nbin*(ihydro-1) )**2.0_rp )
1611  enddo
1612  sum3 = max( sum3, 0.0_rp )
1613  sum2 = max( sum2, 0.0_rp )
1614  if ( sum2 == 0.0_rp ) then
1615  re_tmp(ihydro) = 0.0_rp
1616  else
1617  re_tmp(ihydro) = sum3 / sum2 * um2cm
1618  end if
1619  end do
1620 
1621  re(k,i,j,i_hi) = ( re_tmp(i_mp_qcl) * sum0(i_mp_qcl) &
1622  + re_tmp(i_mp_qp ) * sum0(i_mp_qp ) &
1623  + re_tmp(i_mp_qd ) * sum0(i_mp_qd ) ) &
1624  / ( sum0(i_mp_qcl) + sum0(i_mp_qp) + sum0(i_mp_qd) + eps )
1625  re(k,i,j,i_hs) = re_tmp(i_mp_qs)
1626  re(k,i,j,i_hg) = re_tmp(i_mp_qg)
1627  re(k,i,j,i_hh) = re_tmp(i_mp_qh)
1628 
1629  enddo
1630  enddo
1631  enddo
1632 
1633  end if
1634 
1635  return

References scale_const::const_eps, scale_atmos_hydrometeor::i_hc, scale_atmos_hydrometeor::i_hg, scale_atmos_hydrometeor::i_hh, scale_atmos_hydrometeor::i_hi, scale_atmos_hydrometeor::i_hr, scale_atmos_hydrometeor::i_hs, scale_atmos_hydrometeor::i_qv, scale_atmos_hydrometeor::n_hyd, and nbin.

Referenced by mod_atmos_phy_mp_vars::atmos_phy_mp_vars_get_diagnostic().

Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_qtrc2qhyd()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_qtrc2qhyd ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(rp), dimension(ka,ia,ja,num_hyd), intent(in)  QTRC0,
real(rp), dimension (ka,ia,ja,n_hyd), intent(out)  Qe 
)

Calculate mass ratio of each category.

Definition at line 1646 of file scale_atmos_phy_mp_suzuki10.F90.

1646  use scale_atmos_hydrometeor, only: &
1647  n_hyd, &
1648  i_hc, &
1649  i_hr, &
1650  i_hi, &
1651  i_hs, &
1652  i_hg, &
1653  i_hh
1654  implicit none
1655 
1656  integer, intent(in) :: KA, KS, KE
1657  integer, intent(in) :: IA, IS, IE
1658  integer, intent(in) :: JA, JS, JE
1659  real(RP), intent(in) :: QTRC0(KA,IA,JA,num_hyd) ! tracer mass concentration [kg/kg]
1660  real(RP), intent(out) :: Qe (KA,IA,JA,N_HYD) ! mixing ratio of each cateory [kg/kg]
1661 
1662  integer :: ihydro, ibin, iq, icateg
1663  integer :: k, i, j
1664  !---------------------------------------------------------------------------
1665 
1666 !OCL XFILL
1667  !$omp workshare
1668  qe(:,:,:,:) = 0.0_rp
1669  !$omp end workshare
1670 
1671  do ihydro = 1, nspc
1672  do ibin = 1, nbin
1673  iq = nbin*(ihydro-1) + ibin
1674 
1675  if ( iq > 0 .AND. iq <= nbin*(i_mp_qc ) ) then ! liquid
1676  if ( iq > 0 .AND. iq <= nbnd ) then ! cloud
1677  icateg = i_hc
1678  elseif( iq > nbnd .AND. iq <= nbin ) then ! rain
1679  icateg = i_hr
1680  endif
1681  elseif( iq > nbin*(i_mp_qcl-1) .AND. iq <= nbin*(i_mp_qcl) ) then ! ice (column)
1682  icateg = i_hi
1683  elseif( iq > nbin*(i_mp_qp -1) .AND. iq <= nbin*(i_mp_qp ) ) then ! ice (plate)
1684  icateg = i_hi
1685  elseif( iq > nbin*(i_mp_qd -1) .AND. iq <= nbin*(i_mp_qd ) ) then ! ice (dendrite)
1686  icateg = i_hi
1687  elseif( iq > nbin*(i_mp_qs -1) .AND. iq <= nbin*(i_mp_qs ) ) then ! snow
1688  icateg = i_hs
1689  elseif( iq > nbin*(i_mp_qg -1) .AND. iq <= nbin*(i_mp_qg ) ) then ! graupel
1690  icateg = i_hg
1691  elseif( iq > nbin*(i_mp_qh -1) .AND. iq <= num_hyd ) then ! hail
1692  icateg = i_hh
1693  endif
1694 
1695  !$omp parallel do collapse(2)
1696  do j = js, je
1697  do i = is, ie
1698  do k = ks, ke
1699  qe(k,i,j,icateg) = qe(k,i,j,icateg) + qtrc0(k,i,j,iq)
1700  enddo
1701  enddo
1702  enddo
1703  enddo
1704  enddo
1705 
1706  return

References scale_atmos_hydrometeor::i_hc, scale_atmos_hydrometeor::i_hg, scale_atmos_hydrometeor::i_hh, scale_atmos_hydrometeor::i_hi, scale_atmos_hydrometeor::i_hr, scale_atmos_hydrometeor::i_hs, scale_atmos_hydrometeor::n_hyd, and nbin.

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_calc_tendency(), and mod_atmos_phy_mp_vars::atmos_phy_mp_vars_get_diagnostic().

Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_qtrc2nhyd()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_qtrc2nhyd ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(rp), dimension (ka,ia,ja), intent(in)  DENS,
real(rp), dimension(ka,ia,ja,num_hyd), intent(in)  QTRC0,
real(rp), dimension (ka,ia,ja,n_hyd), intent(out)  Ne 
)

Calculate number concentration of each category.

Definition at line 1717 of file scale_atmos_phy_mp_suzuki10.F90.

1717  use scale_atmos_hydrometeor, only: &
1718  n_hyd, &
1719  i_hc, &
1720  i_hr, &
1721  i_hi, &
1722  i_hs, &
1723  i_hg, &
1724  i_hh
1725  implicit none
1726 
1727  integer, intent(in) :: KA, KS, KE
1728  integer, intent(in) :: IA, IS, IE
1729  integer, intent(in) :: JA, JS, JE
1730  real(RP), intent(in) :: DENS (KA,IA,JA) ! density [kg/m3]
1731  real(RP), intent(in) :: QTRC0(KA,IA,JA,num_hyd) ! tracer mass concentration [kg/kg]
1732  real(RP), intent(out) :: Ne (KA,IA,JA,N_HYD) ! number concentration of each cateory [1/m3]
1733 
1734  integer :: ihydro, ibin, iq, icateg
1735  integer :: k, i, j
1736  !---------------------------------------------------------------------------
1737 
1738 !OCL XFILL
1739  !$omp workshare
1740  ne(:,:,:,:) = 0.0_rp
1741  !$omp end workshare
1742 
1743  do ihydro = 1, nspc
1744  do ibin = 1, nbin
1745  iq = nbin*(ihydro-1) + ibin
1746 
1747  if ( iq > 0 .AND. iq <= nbin*(i_mp_qc ) ) then ! liquid
1748  if ( iq > 0 .AND. iq <= nbnd ) then ! cloud
1749  icateg = i_hc
1750  elseif( iq > nbnd .AND. iq <= nbin ) then ! rain
1751  icateg = i_hr
1752  endif
1753  elseif( iq > nbin*(i_mp_qcl-1) .AND. iq <= nbin*(i_mp_qcl) ) then ! ice (column)
1754  icateg = i_hi
1755  elseif( iq > nbin*(i_mp_qp -1) .AND. iq <= nbin*(i_mp_qp ) ) then ! ice (plate)
1756  icateg = i_hi
1757  elseif( iq > nbin*(i_mp_qd -1) .AND. iq <= nbin*(i_mp_qd ) ) then ! ice (dendrite)
1758  icateg = i_hi
1759  elseif( iq > nbin*(i_mp_qs -1) .AND. iq <= nbin*(i_mp_qs ) ) then ! snow
1760  icateg = i_hs
1761  elseif( iq > nbin*(i_mp_qg -1) .AND. iq <= nbin*(i_mp_qg ) ) then ! graupel
1762  icateg = i_hg
1763  elseif( iq > nbin*(i_mp_qh -1) .AND. iq <= num_hyd ) then ! hail
1764  icateg = i_hh
1765  endif
1766 
1767  !$omp parallel do collapse(2)
1768  do j = js, je
1769  do i = is, ie
1770  do k = ks, ke
1771  ne(k,i,j,icateg) = ne(k,i,j,icateg) + dens(k,i,j) * qtrc0(k,i,j,iq) * rexpxctr(ibin)
1772  enddo
1773  enddo
1774  enddo
1775  enddo
1776  enddo
1777 
1778  return

References scale_atmos_hydrometeor::i_hc, scale_atmos_hydrometeor::i_hg, scale_atmos_hydrometeor::i_hh, scale_atmos_hydrometeor::i_hi, scale_atmos_hydrometeor::i_hr, scale_atmos_hydrometeor::i_hs, scale_atmos_hydrometeor::n_hyd, and nbin.

Referenced by mod_atmos_phy_mp_vars::atmos_phy_mp_vars_get_diagnostic().

Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_qhyd2qtrc()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_qhyd2qtrc ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(rp), dimension(ka,ia,ja,n_hyd), intent(in)  Qe,
real(rp), dimension(ka,ia,ja,qa-1), intent(out)  QTRC,
real(rp), dimension(ka,ia,ja,n_hyd), intent(in), optional  QNUM 
)

get mass ratio of each category

Definition at line 1788 of file scale_atmos_phy_mp_suzuki10.F90.

1788  use scale_const, only: &
1789  pi => const_pi, &
1790  eps => const_eps
1791  use scale_atmos_hydrometeor, only: &
1792  n_hyd, &
1793  i_hc, &
1794  i_hr, &
1795  i_hi, &
1796  i_hs, &
1797  i_hg, &
1798  i_hh
1799  use scale_specfunc, only: &
1800  sf_gamma
1801  implicit none
1802  integer, intent(in) :: KA, KS, KE
1803  integer, intent(in) :: IA, IS, IE
1804  integer, intent(in) :: JA, JS, JE
1805 
1806  real(RP), intent(in) :: Qe(KA,IA,JA,N_HYD) ! mass ratio of each cateory [kg/kg]
1807 
1808  real(RP), intent(out) :: QTRC(KA,IA,JA,QA-1)
1809 
1810  real(RP), intent(in), optional :: QNUM(KA,IA,JA,N_HYD) ! number concentratio
1811 
1812  real(RP) :: coef0, coef1, coef2
1813  real(RP) :: dummy(nbin)
1814  real(RP) :: tmp_hyd, num_hyd_l, lambda_hyd
1815 
1816  integer :: k, i, j, iq
1817 
1818  if ( present(qnum) ) then
1819  log_warn("ATMOS_PHY_MP_suzuki10_qhyd2qtrc",*) 'At this moment, number concentratio is ignored'
1820  end if
1821 
1822  !--- define coefficients
1823  coef0 = 4.0_rp/3.0_rp*pi
1824  coef1 = 4.0_rp/3.0_rp*sqrt(pi/2.0_rp)
1825 
1826  if( nspc == 1 ) then !--- put all hydrometeors to liquid (warm bin)
1827 
1828  !$omp parallel do private(tmp_hyd,dummy,coef2)
1829  do j = js, je
1830  do i = is, ie
1831  do k = ks, ke
1832 
1833  tmp_hyd = 0.0_rp
1834  do iq = 1, nbin
1835  dummy(iq) = coef1 / sigma_sdf(1) * rho_sdf(1) * radc( iq )**3 &
1836  * exp( &
1837  - ( log( radc(iq) )-log( r0_sdf(1) ) )**2*0.5_rp &
1838  / sigma_sdf(1) / sigma_sdf(1) &
1839  )
1840  tmp_hyd = tmp_hyd + dummy(iq)
1841  enddo
1842 
1843  coef2 = ( qe(k,i,j,i_hc) + qe(k,i,j,i_hr) &
1844  + qe(k,i,j,i_hi) + qe(k,i,j,i_hs) + qe(k,i,j,i_hg) ) &
1845  / ( tmp_hyd + ( 0.50_rp - sign(0.50_rp,tmp_hyd-eps) ) )
1846 
1847  do iq = 1, nbin
1848  qtrc(k+2,i,j,(il-1)*nbin+iq) = coef2 * dummy(iq)
1849  enddo
1850 
1851  enddo
1852  enddo
1853  enddo
1854 
1855  elseif( nspc > 1 ) then !--- put each hydrometeor to each category (ice bin)
1856 
1857  !$omp parallel do private(tmp_hyd,dummy,coef2,num_hyd_l,lambda_hyd)
1858  do j = js, je
1859  do i = is, ie
1860  do k = ks, ke
1861 
1862  !--- Rain and Cloud put into liquid bin (log-normal)
1863  tmp_hyd = 0.0_rp
1864  do iq = 1, nbin
1865  dummy(iq) = coef1 / sigma_sdf(1) * rho_sdf(1) * radc( iq )**3 &
1866  * exp( &
1867  - ( log( radc(iq) )-log( r0_sdf(1) ) )**2*0.5_rp &
1868  / sigma_sdf(1) / sigma_sdf(1) &
1869  )
1870  tmp_hyd = tmp_hyd + dummy(iq)
1871  enddo
1872 
1873  coef2 = ( qe(k,i,j,i_hc) + qe(k,i,j,i_hr) ) &
1874  / ( tmp_hyd + ( 0.50_rp - sign(0.50_rp,tmp_hyd-eps) ) )
1875 
1876  do iq = 1, nbin
1877  qtrc(k,i,j,(il-1)*nbin+iq) = coef2 * dummy(iq)
1878  enddo
1879 
1880  !--- Ice put into plate bin (log-normal)
1881  tmp_hyd = 0.0_rp
1882  do iq = 1, nbin
1883  dummy(iq) = coef1 / sigma_sdf(2) * rho_sdf(2) * radc( iq )**3 &
1884  * exp( &
1885  - ( log( radc(iq) )-log( r0_sdf(2) ) )**2*0.5_rp &
1886  / sigma_sdf(2) / sigma_sdf(2) &
1887  )
1888  tmp_hyd = tmp_hyd + dummy(iq)
1889  enddo
1890 
1891  coef2 = ( qe(k,i,j,i_hi) ) &
1892  / ( tmp_hyd + ( 0.50_rp - sign(0.50_rp,tmp_hyd-eps) ) )
1893 
1894  do iq = 1, nbin
1895  qtrc(k,i,j,(ic-1)*nbin+iq) = 0.0_rp
1896  qtrc(k,i,j,(ip-1)*nbin+iq) = coef2 * dummy(iq)
1897  qtrc(k,i,j,(id-1)*nbin+iq) = 0.0_rp
1898  enddo
1899 
1900  !--- Snow put into snow bin (gamma)
1901  num_hyd_l = coef0 * n0_sdf(3) * rho_sdf(3)
1902  lambda_hyd = ( pi * rho_sdf(3) / 6.0_rp *n0_sdf(3) * sf_gamma(4.0_rp) &
1903  / ( qe(k,i,j,i_hs) &
1904  + (0.50_rp-sign(0.50_rp,qe(k,i,j,i_hs)-eps)) &
1905  ) )**(0.25_rp)
1906 
1907  tmp_hyd = 0.0_rp
1908  do iq = 1, nbin
1909  dummy(iq) = num_hyd_l * radc( iq )**3 &
1910  * exp( -lambda_hyd * 0.5_rp * radc( iq ) )
1911  tmp_hyd = tmp_hyd + dummy(iq)
1912  enddo
1913 
1914  coef2 = ( qe(k,i,j,i_hs) ) &
1915  / ( tmp_hyd + ( 0.50_rp - sign(0.50_rp,tmp_hyd-eps) ) )
1916 
1917  do iq = 1, nbin
1918  qtrc(k,i,j,(iss-1)*nbin+iq) = coef2 * dummy(iq)
1919  enddo
1920 
1921  !--- Graupel put into Graupel bin (gamma)
1922  num_hyd_l = coef0 * n0_sdf(4) * rho_sdf(4)
1923  lambda_hyd = ( pi * rho_sdf(4) / 6.0_rp *n0_sdf(4) * sf_gamma(4.0_rp) &
1924  / ( qe(k,i,j,i_hg) &
1925  + (0.50_rp-sign(0.50_rp,qe(k,i,j,i_hg)-eps)) &
1926  ) )**(0.25_rp)
1927 
1928  tmp_hyd = 0.0_rp
1929  do iq = 1, nbin
1930  dummy(iq) = num_hyd_l * radc( iq )**3 &
1931  * exp( -lambda_hyd * 0.5_rp * radc( iq ) )
1932  tmp_hyd = tmp_hyd + dummy(iq)
1933  enddo
1934 
1935  coef2 = ( qe(k,i,j,i_hg) ) &
1936  / ( tmp_hyd + ( 0.50_rp - sign(0.50_rp,tmp_hyd-eps) ) )
1937 
1938  do iq = 1, nbin
1939  qtrc(k,i,j,(ig-1)*nbin+iq) = coef2 * dummy(iq)
1940  enddo
1941 
1942  !--- Hail put into Hail bin (gamma)
1943  num_hyd_l = coef0 * n0_sdf(5) * rho_sdf(5)
1944  lambda_hyd = ( pi * rho_sdf(5) / 6.0_rp *n0_sdf(5) * sf_gamma(4.0_rp) &
1945  / ( qe(k,i,j,i_hh) &
1946  + (0.50_rp-sign(0.50_rp,qe(k,i,j,i_hh)-eps)) &
1947  ) )**(0.25_rp)
1948 
1949  tmp_hyd = 0.0_rp
1950  do iq = 1, nbin
1951  dummy(iq) = num_hyd_l * radc( iq )**3 &
1952  * exp( -lambda_hyd * 0.5_rp * radc( iq ) )
1953  tmp_hyd = tmp_hyd + dummy(iq)
1954  enddo
1955 
1956  coef2 = ( qe(k,i,j,i_hh) ) &
1957  / ( tmp_hyd + ( 0.50_rp - sign(0.50_rp,tmp_hyd-eps) ) )
1958 
1959  do iq = 1, nbin
1960  qtrc(k,i,j,(ih-1)*nbin+iq) = coef2 * dummy(iq)
1961  enddo
1962 
1963  enddo
1964  enddo
1965  enddo
1966 
1967  endif
1968 
1969  !$omp parallel do collapse(3)
1970  do iq = num_hyd+1, qa-1
1971  do j = js, je
1972  do i = is, ie
1973  do k = ks, ke
1974  qtrc(k,i,j,iq) = 0.0_rp
1975  end do
1976  end do
1977  end do
1978  end do
1979 
1980  return

References scale_const::const_eps, scale_const::const_pi, scale_atmos_hydrometeor::i_hc, scale_atmos_hydrometeor::i_hg, scale_atmos_hydrometeor::i_hh, scale_atmos_hydrometeor::i_hi, scale_atmos_hydrometeor::i_hr, scale_atmos_hydrometeor::i_hs, scale_atmos_hydrometeor::n_hyd, nbin, and scale_specfunc::sf_gamma().

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_qhyd2qtrc().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ atmos_phy_mp_suzuki10_crg_qtrc2qhyd()

subroutine, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_crg_qtrc2qhyd ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
real(rp), dimension(ka,ia,ja,num_hyd), intent(in)  QTRC0,
real(rp), dimension(ka,ia,ja,n_hyd), intent(out)  Qecrg 
)

get charge density ratio of each category

Definition at line 1991 of file scale_atmos_phy_mp_suzuki10.F90.

1991  use scale_atmos_hydrometeor, only: &
1992  n_hyd, &
1993  i_hc, &
1994  i_hr, &
1995  i_hi, &
1996  i_hs, &
1997  i_hg, &
1998  i_hh
1999  implicit none
2000 
2001  integer, intent(in) :: KA, KS, KE
2002  integer, intent(in) :: IA, IS, IE
2003  integer, intent(in) :: JA, JS, JE
2004  real(RP), intent(in) :: QTRC0(KA,IA,JA,num_hyd) ! tracer charge density [fC/kg]
2005  real(RP), intent(out) :: Qecrg(KA,IA,JA,N_HYD) ! charge density ratio of each cateory [fC/kg]
2006 
2007  integer :: ihydro, ibin, iq, icateg
2008  integer :: k, i, j
2009  !---------------------------------------------------------------------------
2010 
2011 !OCL XFILL
2012  !$omp workshare
2013  qecrg(:,:,:,:) = 0.0_rp
2014  !$omp end workshare
2015 
2016  do ihydro = 1, nspc
2017  do ibin = 1, nbin
2018  iq = nbin*(ihydro-1) + ibin
2019 
2020  if ( iq > 0 .AND. iq <= nbin*(i_mp_qc ) ) then ! liquid
2021  if ( iq > 0 .AND. iq <= nbnd ) then ! cloud
2022  icateg = i_hc
2023  elseif( iq > nbnd .AND. iq <= nbin ) then ! rain
2024  icateg = i_hr
2025  endif
2026  elseif( iq > nbin*(i_mp_qcl-1) .AND. iq <= nbin*(i_mp_qcl) ) then ! ice (column)
2027  icateg = i_hi
2028  elseif( iq > nbin*(i_mp_qp -1) .AND. iq <= nbin*(i_mp_qp ) ) then ! ice (plate)
2029  icateg = i_hi
2030  elseif( iq > nbin*(i_mp_qd -1) .AND. iq <= nbin*(i_mp_qd ) ) then ! ice (dendrite)
2031  icateg = i_hi
2032  elseif( iq > nbin*(i_mp_qs -1) .AND. iq <= nbin*(i_mp_qs ) ) then ! snow
2033  icateg = i_hs
2034  elseif( iq > nbin*(i_mp_qg -1) .AND. iq <= nbin*(i_mp_qg ) ) then ! graupel
2035  icateg = i_hg
2036  elseif( iq > nbin*(i_mp_qh -1) .AND. iq <= num_hyd ) then ! hail
2037  icateg = i_hh
2038  endif
2039 
2040  !$omp parallel do collapse(2)
2041  do j = js, je
2042  do i = is, ie
2043  do k = ks, ke
2044  qecrg(k,i,j,icateg) = qecrg(k,i,j,icateg) + qtrc0(k,i,j,iq)
2045  enddo
2046  enddo
2047  enddo
2048  enddo
2049  enddo
2050 
2051  return

References scale_const::const_dwatr, scale_const::const_emelt, scale_const::const_eps, scale_const::const_pi, scale_const::const_psat0, scale_const::const_rvap, scale_const::const_tem00, scale_const::const_tmelt, scale_atmos_hydrometeor::cp_ice, scale_atmos_hydrometeor::cp_vapor, scale_atmos_hydrometeor::cp_water, scale_atmos_hydrometeor::cv_ice, scale_atmos_hydrometeor::cv_vapor, scale_atmos_hydrometeor::cv_water, scale_atmos_hydrometeor::i_hc, scale_atmos_hydrometeor::i_hg, scale_atmos_hydrometeor::i_hh, scale_atmos_hydrometeor::i_hi, scale_atmos_hydrometeor::i_hr, scale_atmos_hydrometeor::i_hs, scale_atmos_hydrometeor::n_hyd, nbin, nccn, scale_prc::prc_abort(), scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_calc_tendency().

Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ atmos_phy_mp_suzuki10_ntracers

integer, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_ntracers

Definition at line 56 of file scale_atmos_phy_mp_suzuki10.F90.

56  integer, public :: ATMOS_PHY_MP_suzuki10_ntracers

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_tracer_setup(), and atmos_phy_mp_suzuki10_tracer_setup().

◆ atmos_phy_mp_suzuki10_nwaters

integer, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_nwaters

◆ atmos_phy_mp_suzuki10_nices

integer, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_nices

◆ atmos_phy_mp_suzuki10_nccn

integer, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_nccn

◆ atmos_phy_mp_suzuki10_nbnd

integer, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_nbnd

Definition at line 60 of file scale_atmos_phy_mp_suzuki10.F90.

60  integer, public :: ATMOS_PHY_MP_suzuki10_nbnd

Referenced by atmos_phy_mp_suzuki10_setup().

◆ atmos_phy_mp_suzuki10_tracer_names

character(len=h_short), dimension(:), allocatable, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_tracer_names

Definition at line 63 of file scale_atmos_phy_mp_suzuki10.F90.

63  character(len=H_SHORT), public, allocatable :: ATMOS_PHY_MP_suzuki10_tracer_names(:)

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_tracer_setup(), atmos_phy_mp_suzuki10_finalize(), and atmos_phy_mp_suzuki10_tracer_setup().

◆ atmos_phy_mp_suzuki10_tracer_descriptions

character(len=h_mid), dimension(:), allocatable, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_tracer_descriptions

Definition at line 64 of file scale_atmos_phy_mp_suzuki10.F90.

64  character(len=H_MID) , public, allocatable :: ATMOS_PHY_MP_suzuki10_tracer_descriptions(:)

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_tracer_setup(), atmos_phy_mp_suzuki10_finalize(), and atmos_phy_mp_suzuki10_tracer_setup().

◆ atmos_phy_mp_suzuki10_tracer_units

character(len=h_short), dimension(:), allocatable, public scale_atmos_phy_mp_suzuki10::atmos_phy_mp_suzuki10_tracer_units

Definition at line 65 of file scale_atmos_phy_mp_suzuki10.F90.

65  character(len=H_SHORT), public, allocatable :: ATMOS_PHY_MP_suzuki10_tracer_units(:)

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_tracer_setup(), atmos_phy_mp_suzuki10_finalize(), and atmos_phy_mp_suzuki10_tracer_setup().

◆ nbin

integer, public scale_atmos_phy_mp_suzuki10::nbin = 33

◆ nccn

integer, public scale_atmos_phy_mp_suzuki10::nccn = 0
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_atmos_hydrometeor::i_hr
integer, parameter, public i_hr
liquid water rain
Definition: scale_atmos_hydrometeor.F90:98
scale_atmos_hydrometeor::i_hs
integer, parameter, public i_hs
snow
Definition: scale_atmos_hydrometeor.F90:100
scale_const::const_eps
real(rp), public const_eps
small number
Definition: scale_const.F90:35
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
scale_atmos_hydrometeor::i_hh
integer, parameter, public i_hh
hail
Definition: scale_atmos_hydrometeor.F90:102
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_atmos_hydrometeor::i_hi
integer, parameter, public i_hi
ice water cloud
Definition: scale_atmos_hydrometeor.F90:99
scale_prc::prc_masterrank
integer, parameter, public prc_masterrank
master process in each communicator
Definition: scale_prc.F90:67
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_specfunc
module SPECFUNC
Definition: scale_specfunc.F90:14
scale_const::const_pi
real(rp), parameter, public const_pi
pi
Definition: scale_const.F90:32
scale_atmos_hydrometeor::i_hc
integer, parameter, public i_hc
liquid water cloud
Definition: scale_atmos_hydrometeor.F90:97
scale_const::const_dwatr
real(rp), parameter, public const_dwatr
density of water [kg/m3]
Definition: scale_const.F90:89
scale_const::const_tem00
real(rp), parameter, public const_tem00
temperature reference (0C) [K]
Definition: scale_const.F90:99
scale_comm_cartesc
module COMMUNICATION
Definition: scale_comm_cartesC.F90:11
scale_const::const_dice
real(rp), parameter, public const_dice
density of ice [kg/m3]
Definition: scale_const.F90:90
scale_specfunc::sf_gamma
real(rp) function, public sf_gamma(x)
Gamma function.
Definition: scale_specfunc.F90:50
scale_atmos_saturation
module atmosphere / saturation
Definition: scale_atmos_saturation.F90:12
scale_prc::prc_ismaster
logical, public prc_ismaster
master process in local communicator?
Definition: scale_prc.F90:92
scale_atmos_hydrometeor::i_hg
integer, parameter, public i_hg
graupel
Definition: scale_atmos_hydrometeor.F90:101