Class | saturation_adjust |
In: |
lscond/saturation_adjust.f90
|
Note that Japanese and English are described in parallel.
Adjust temperature and specific humidity by the use of saturation adjustment
!$ ! Manabe, S., J. Smagorinsky, R. F. Strickler, !$ ! Simulated climatology of a general circulation model with a hydrologic cycle, !$ ! Mon. Wea. Rev., 93, 769-798, 1965.
SaturationAdjust : | æ¸�º¦���湿ã���ç¯� |
—————- : | ———— |
SaturationAdjust : | Adjust temperature and specific humidity |
Subroutine : | |||
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(inout)
| ||
xyz_QVap(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(inout)
| ||
xyz_QH2OLiq(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in )
| ||
xyz_Press(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in)
| ||
xyr_Press(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in)
| ||
xyz_DQH2OLiqDt(0:imax-1,1:jmax,1:kmax) : | real(DP), intent(out) |
Adjust temperature and specific humidity by the use of saturation adjustment
subroutine SaturationAdjust( xyz_Temp, xyz_QVap, xyz_QH2OLiq, xyz_Press, xyr_Press, xyz_DQH2OLiqDt ) ! ! ! ! Adjust temperature and specific humidity by the use of saturation ! adjustment ! ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements ! ! ����å®��°è¨å®� ! Physical constants settings ! use constants, only: Grav, CpDry, LatentHeat, LatentHeatFusion ! $ L $ [J kg-1] . ! ��解ã�����. ! Latent heat of fusion ! ���»ç��� ! Time control ! use timeset, only: DelTime, TimeN, TimesetClockStart, TimesetClockStop ! ���¹ã�������¼ã�¿å�ºå�� ! History data output ! use gtool_historyauto, only: HistoryAutoPut ! 飽å��æ¯�湿ã����� ! Evaluate saturation specific humidity ! use saturate, only: xyz_CalcQVapSat ! 大è�模å��çµ� (��対æ��§å��çµ�) (Manabe, 1965) ! Large scale condensation (non-convective condensation) (Le Treut and Li, 1991) use lscond, only : LScaleCond ! 宣è��� ; Declaration statements ! implicit none real(DP), intent(inout):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax) ! $ T $ . æ¸�º¦. Temperature real(DP), intent(inout):: xyz_QVap (0:imax-1, 1:jmax, 1:kmax) ! $ q $ . æ¯�æ¹�. Specific humidity real(DP), intent(in ):: xyz_QH2OLiq(0:imax-1, 1:jmax, 1:kmax) ! $ q_w $ . �²æ°´æ··å��æ¯�. Cloud water mixing ratio real(DP), intent(in):: xyz_Press (0:imax-1, 1:jmax, 1:kmax) ! $ p $ . æ°��� (�´æ�°ã������). ! Air pressure (full level) real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax) ! $ \hat{p} $ . æ°��� (���´æ�°ã������). ! Air pressure (half level) real(DP), intent(out) :: xyz_DQH2OLiqDt(0:imax-1,1:jmax,1:kmax) ! ä½�æ¥å��� ! Work variables ! real(DP):: xyz_QVapSat (0:imax-1, 1:jmax, 1:kmax) ! 飽å��æ¯�æ¹�. ! Saturation specific humidity. real(DP):: xy_RainLsc (0:imax-1, 1:jmax) ! ��æ°´é��. ! Precipitation real(DP):: xyz_DTempDtLsc (0:imax-1, 1:jmax, 1:kmax) ! æ¸�º¦å¤�����. ! Temperature tendency real(DP):: xyz_DQVapDtLsc (0:imax-1, 1:jmax, 1:kmax) ! æ¯�湿å�����. ! Specific humidity tendency real(DP):: xyz_QVapB (0:imax-1, 1:jmax, 1:kmax) ! 調ç������æ¹�. ! Specific humidity before adjust. real(DP):: xyz_QH2OLiqB (0:imax-1, 1:jmax, 1:kmax) ! 調ç������²æ°´æ··å��æ¯�. ! Mixing ratio of cloud water before adjust. real(DP):: xyz_TempB (0:imax-1, 1:jmax, 1:kmax) ! 調ç�����¸©åº�. ! Temperature before adjust. ! real(DP):: xyz_RainLSC(0:imax-1, 1:jmax, 1:kmax) real(DP):: xyz_EvapQH2OLiq(0:imax-1, 1:jmax, 1:kmax) real(DP):: TempTentative real(DP):: LatentHeatLocal ! ! Latent heat used in this routine integer:: i integer:: j integer:: k ! ���´æ�¹å�������� DO ���¼ã�����æ¥å��� ! Work variables for DO loop in vertical direction ! å®�è¡��� ; Executable statement ! ! ������確è� ! Initialization check ! if ( .not. saturation_adjust_inited ) then call MessageNotify( 'E', module_name, 'This module has not been initialized.' ) end if ! è¨�ç®�����è¨�æ¸���å§� ! Start measurement of computation time ! call TimesetClockStart( module_name ) ! Set a value for latent heat if ( FlagSublimation ) then LatentHeatLocal = LatentHeat + LatentHeatFusion else LatentHeatLocal = LatentHeat end if ! 調ç��� "QVap", "QH2OLiq", "Temp" ���å� ! Store "QVap", "QH2OLiq", "Temp" before adjustment ! xyz_QVapB = xyz_QVap xyz_QH2OLiqB = xyz_QH2OLiq xyz_TempB = xyz_Temp ! 飽å��æ¯�湿è�ç®� ! Calculate saturation specific humidity ! xyz_QVapSat = xyz_CalcQVapSat( xyz_Temp, xyz_Press ) ! Evaporate all of cloud liquid water temporarily !!$ xyz_EvapQH2OLiq = xyz_QH2OLiq ! Evaporate part of cloud liquid water temporarily do k = 1, kmax do j = 1, jmax do i = 0, imax-1 xyz_EvapQH2OLiq(i,j,k) = min( max( xyz_QVapSat(i,j,k), xyz_QVap(i,j,k) ) - xyz_QVap(i,j,k), xyz_QH2OLiq(i,j,k) ) xyz_EvapQH2OLiq(i,j,k) = xyz_EvapQH2OLiq(i,j,k) * ( 1.0_DP - 1.0e-10_DP ) TempTentative = xyz_Temp(i,j,k) - LatentHeatLocal * xyz_EvapQH2OLiq(i,j,k) / CpDry if ( TempTentative < 1.0_DP ) then TempTentative = 1.0_DP xyz_EvapQH2OLiq(i,j,k) = ( xyz_Temp(i,j,k) - TempTentative ) / ( LatentHeatLocal / CpDry ) end if end do end do end do ! xyz_Temp = xyz_Temp - LatentHeatLocal * xyz_EvapQH2OLiq / CpDry xyz_QVap = xyz_QVap + xyz_EvapQH2OLiq ! QH2OLiq will be updated in cloud model. Tendency will be updated below. !!$ xyz_QH2OLiq = 0.0_DP call LScaleCond( xyz_Temp, xyz_QVap, xyz_Press, xyr_Press, xyz_DQH2OLiqDt, .false. ) ! æ¯�湿å�����, æ¸�º¦å¤�����, ��æ°´é������ ! Calculate specific humidity tendency, temperature tendency, ! precipitation ! xyz_DQVapDtLsc = ( xyz_QVap - xyz_QVapB ) / ( 2.0_DP * DelTime ) xyz_DTempDtLsc = ( xyz_Temp - xyz_TempB ) / ( 2.0_DP * DelTime ) xyz_DQH2OLiqDt = xyz_DQH2OLiqDt - xyz_EvapQH2OLiq / ( 2.0_DP * DelTime ) ! calculation for output xy_RainLsc = 0.0_DP do k = kmax, 1, -1 xy_RainLsc = xy_RainLsc + xyz_DQH2OLiqDt(:,:,k) * ( xyr_Press(:,:,k-1) - xyr_Press(:,:,k) ) / Grav end do ! ���¹ã�������¼ã�¿å�ºå�� ! History data output ! call HistoryAutoPut( TimeN, 'RainLsc', xy_RainLsc ) call HistoryAutoPut( TimeN, 'DTempDtLsc', xyz_DTempDtLsc ) call HistoryAutoPut( TimeN, 'DQVapDtLsc', xyz_DQVapDtLsc ) ! è¨�ç®�����è¨�æ¸������æ� ! Pause measurement of computation time ! call TimesetClockStop( module_name ) end subroutine SaturationAdjust
Subroutine : | |
FlagSnow : | logical, intent(in) |
saturation_adjust �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. NAMELIST#saturation_adjust_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��.
"saturation_adjust" module is initialized. "NAMELIST#saturation_adjust_nml" is loaded in this procedure.
This procedure input/output NAMELIST#saturation_adjust_nml .
subroutine SaturationAdjustInit( FlagSnow ) ! ! saturation_adjust �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. ! NAMELIST#saturation_adjust_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��. ! ! "saturation_adjust" module is initialized. ! "NAMELIST#saturation_adjust_nml" is loaded in this procedure. ! ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements ! ! NAMELIST ���¡ã�¤ã���¥å�����¢ã�������¼ã���£ã������ ! Utilities for NAMELIST file input ! use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid ! ���¡ã�¤ã���¥å�ºå��è£��� ! File I/O support ! use dc_iounit, only: FileOpen ! ç¨��¥å�������¡ã�� ! Kind type parameter ! use dc_types, only: STDOUT ! æ¨�æº��ºå�����ç½����. Unit number of standard output ! ��å�����ä½� ! Character handling ! use dc_string, only: StoA ! ���¹ã�������¼ã�¿å�ºå�� ! History data output ! use gtool_historyauto, only: HistoryAutoAddVariable ! 飽å��æ¯�湿ã����� ! Evaluate saturation specific humidity ! use saturate, only: SaturateInit ! 大è�模å��çµ� (��対æ��§å��çµ�) (Manabe, 1965) ! Large scale condensation (non-convective condensation) (Le Treut and Li, 1991) use lscond, only : LScaleCondInit ! 宣è��� ; Declaration statements ! implicit none logical, intent(in) :: FlagSnow integer:: unit_nml ! NAMELIST ���¡ã�¤ã�����¼ã���³ç���ç½����. ! Unit number for NAMELIST file open integer:: iostat_nml ! NAMELIST èªã�¿è¾¼�¿æ���� IOSTAT. ! IOSTAT of NAMELIST read ! NAMELIST å¤��°ç¾¤ ! NAMELIST group name ! namelist /saturation_adjust_nml/ FlagSublimation ! ! �����������¤ã���¤ã��������������ç¶� "saturation_adjust#SaturationAdjustInit" ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. ! ! Refer to source codes in the initialization procedure ! "saturation_adjust#SaturationAdjustInit" for the default values. ! ! å®�è¡��� ; Executable statement ! if ( saturation_adjust_inited ) return ! �����������¤ã��¨å®� ! Default values settings ! FlagSublimation = .false. ! NAMELIST ����¿è¾¼�� ! NAMELIST is input ! if ( trim(namelist_filename) /= '' ) then call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in) rewind( unit_nml ) read( unit_nml, nml = saturation_adjust_nml, iostat = iostat_nml ) ! (out) close( unit_nml ) call NmlutilMsg( iostat_nml, module_name ) ! (in) if ( iostat_nml == 0 ) write( STDOUT, nml = saturation_adjust_nml ) end if ! Initialization of modules used in this routine ! 飽å��æ¯�湿ã����� ! Evaluate saturation specific humidity ! call SaturateInit ! 大è�模å��çµ� (��対æ��§å��çµ�) (Manabe, 1965) ! Large scale condensation (non-convective condensation) (Le Treut and Li, 1991) ! call LScaleCondInit( FlagSnow ) ! ���¹ã�������¼ã�¿å�ºå�����������¸ã����°ç�»é�� ! Register of variables for history data output ! ! HistoryAutoAddVariable is called in LScaleCond for variables below. ! !!$ call HistoryAutoAddVariable( 'RainLsc', & !!$ & (/ 'lon ', 'lat ', 'time' /), & !!$ & 'precipitation by large scale condensation', 'kg m-2 s-1' ) !!$ call HistoryAutoAddVariable( 'DTempDtLsc', & !!$ & (/ 'lon ', 'lat ', 'sig ', 'time' /), & !!$ & 'large-scale condensation heating', 'K s-1' ) !!$ call HistoryAutoAddVariable( 'DQVapDtLsc', & !!$ & (/ 'lon ', 'lat ', 'sig ', 'time' /), & !!$ & 'large-scale condensation moistening', 'kg kg-1 s-1' ) ! �°å� ; Print ! call MessageNotify( 'M', module_name, '----- Initialization Messages -----' ) call MessageNotify( 'M', module_name, ' FlagSublimation = %b', l = (/ FlagSublimation /) ) call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) ) saturation_adjust_inited = .true. end subroutine SaturationAdjustInit
Constant : | |||
module_name = ‘saturation_adjust‘ : | character(*), parameter
|
Variable : | |||
saturation_adjust_inited = .false. : | logical, save
|
Constant : | |||
version = ’$Name: $’ // ’$Id: saturation_adjust.f90,v 1.4 2015/01/29 12:03:22 yot Exp $’ : | character(*), parameter
|