!= Module MoistBuoyancy ! ! Authors:: SUGIYAMA Ko-ichiro ! Version:: $Id: moistbuoyancy.f90,v 1.2 2011-02-23 17:08:00 yamasita Exp $ ! Tag Name:: $Name: $ ! Copyright:: Copyright (C) GFD Dennou Club, 2006. All rights reserved. ! License:: See COPYRIGHT[link:../../COPYRIGHT] ! !== Overview ! ! !== Error Handling ! !== Bugs ! !== Note ! ! !== Future Plans ! ! module MoistBuoyancy ! ! ! !モジュール読み込み use dc_message, only: MessageNotify use gridset, only: SpcNum, &! 化学種の数 & DimXMin, &! x 方向の配列の下限 & DimXMax, &! x 方向の配列の上限 & DimZMin, &! z 方向の配列の下限 & DimZMax, &! z 方向の配列の上限 & DelX, &! x 方向の格子点間隔 & DelZ ! z 方向の格子点間隔 use basicset, only: MolWtDry, &!乾燥成分の分子量 & Grav, &!重力加速度 & SpcWetID, &!凝縮成分のID & MolWtWet, &!凝縮成分の分子量 & CpDry, &!乾燥成分の平均定圧比熱 [J/K kg] & xz_PotTempBasicZ, &!基本場の温位 & xz_EffMolWtBasicZ, &!基本場の分子量効果 & xz_ExnerBasicZ, &!基本場の無次元圧力 & xza_MixRtBasicZ !基本場の混合比 use moistset, only: CondNum, &!凝結過程の数 & IdxCG, &!凝結過程(蒸気)の配列添え字 & IdxCC, &!凝結過程(雲)の配列添え字 & GasNum, &!気体の数 & IdxG, &!気体の配列添え字 & IdxNH3, &!NH3(蒸気)の配列添え字 & IdxH2S !H2S(蒸気)の配列添え字 use ChemCalc, only: xz_LatentHeat, &!潜熱 & ReactHeatNH4SH !NH4SH の反応熱 use average, only: xr_avr_xz, xz_avr_xr use differentiate_center2, only: xr_dz_xz use StoreBuoy, only: StoreBuoyMolWt, StoreBuoyDrag !暗黙の型宣言禁止 implicit none !属性の指定 private !関数を public に設定 public MoistBuoy_Init public xz_BuoyMoistKm public xr_BuoyMolWt public xr_BuoyDrag !変数の定義 real(8) :: Cm = 2.0d-1 real(8) :: MixLen = 0.0d0 real(8), allocatable :: xz_MixRtBasicZPerMolWt(:,:) !基本場の混合比 / 分子量 の総和 real(8), allocatable :: xr_MixRtBasicZPerMolWt(:,:) !基本場の混合比 / 分子量 の総和 real(8), allocatable :: xz_MixRtBasicZ(:,:) !基本場の混合比の総和 real(8), allocatable :: xr_MixRtBasicZ(:,:) !基本場の混合比の総和 save Cm, MixLen save xz_MixRtBasicZPerMolWt save xr_MixRtBasicZPerMolWt save xz_MixRtBasicZ save xr_MixRtBasicZ contains !!!------------------------------------------------------------------!!! subroutine MoistBuoy_Init( ) !暗黙の型宣言禁止 implicit none !変数定義 integer :: s real(8), allocatable :: xza_MixRtBasicZPerMolWt(:,:,:) !基本場の混合比 / 分子量 !----------------------------------------------------------- ! 混合距離 !----------------------------------------------------------- MixLen = sqrt(DelX * DelZ) !----------------------------------------------------------- ! 作業配列の初期化. !----------------------------------------------------------- allocate( & & xza_MixRtBasicZPerMolWt(DimXMin:DimXMax, DimZMin:DimZMax, GasNum), & & xr_MixRtBasicZPerMolWt(DimXMin:DimXMax, DimZMin:DimZMax), & & xz_MixRtBasicZPerMolWt(DimXMin:DimXMax, DimZMin:DimZMax), & & xr_MixRtBasicZ(DimXMin:DimXMax, DimZMin:DimZMax), & & xz_MixRtBasicZ(DimXMin:DimXMax, DimZMin:DimZMax) & & ) xza_MixRtBasicZPerMolWt = 0.0d0 xr_MixRtBasicZPerMolWt = 0.0d0 xz_MixRtBasicZPerMolWt = 0.0d0 xr_MixRtBasicZ = 0.0d0 xz_MixRtBasicZ = 0.0d0 call MessageNotify( "M", & & "MoistBuoy_Init", "MolWtWet = %f", d=(/pack(MolWtWet(:), .true.) /) ) do s = 1, GasNum xza_MixRtBasicZPerMolWt(:,:,s) = & & xza_MixRtBasicZ(:,:,IdxG(s)) / MolWtWet(IdxG(s)) end do xz_MixRtBasicZPerMolWt = sum(xza_MixRtBasicZPerMolWt, 3) xr_MixRtBasicZPerMolWt = xr_avr_xz( sum(xza_MixRtBasicZPerMolWt, 3) ) xz_MixRtBasicZ = sum(xza_MixRtBasicZ, 3) xr_MixRtBasicZ = xr_avr_xz( sum(xza_MixRtBasicZ, 3) ) end subroutine MoistBuoy_Init !!!------------------------------------------------------------------------!!! function xz_BuoyMoistKm(xz_PotTemp, xz_Exner, xza_MixRt) ! !暗黙の型宣言禁止 implicit none !変数定義 real(8), intent(in) :: xz_PotTemp(DimXMin:DimXMax, DimZMin:DimZMax) !温位 real(8), intent(in) :: xz_Exner(DimXMin:DimXMax, DimZMin:DimZMax) !無次元圧力 real(8), intent(in) :: xza_MixRt(DimXMin:DimXMax, DimZMin:DimZMax, SpcNum) !凝縮成分の混合比 real(8) :: xza_MixRtAll(DimXMin:DimXMax, DimZMin:DimZMax, SpcNum) !凝縮成分の混合比 real(8) :: xza_MixRtAll2(DimXMin:DimXMax, DimZMin:DimZMax, SpcNum) !凝縮成分の混合比 real(8) :: xz_BuoyMoistKm(DimXMin:DimXMax, DimZMin:DimZMax) ! real(8) :: xza_LatentHeat(DimXMin:DimXMax, DimZMin:DimZMax, GasNum) !潜熱 real(8) :: xz_TempAll(DimXMin:DimXMax, DimZMin:DimZMax) !温度 real(8) :: xz_EffHeat(DimXMin:DimXMax, DimZMin:DimZMax) ! real(8) :: xz_EffPotTemp(DimXMin:DimXMax, DimZMin:DimZMax) real(8) :: xz_EffMolWt(DimXMin:DimXMax, DimZMin:DimZMax) ! real(8) :: xza_MixRtPerMolWt(DimXMin:DimXMax, DimZMin:DimZMax, GasNum) !混合比/分子量 integer :: s !温度, 圧力, 混合比の全量を求める !擾乱成分と平均成分の足し算 xz_TempAll = ( xz_PotTemp + xz_PotTempBasicZ ) * ( xz_Exner + xz_ExnerBasicZ ) xza_MixRtAll = xza_MixRtBasicZ + xza_MixRt xza_LatentHeat = 0.0d0 !作業配列の初期化. 気体のみ利用 do s = 1, GasNum xza_MixRtPerMolWt(:,:,s) = xza_MixRt(:,:,IdxG(s)) / MolWtWet(IdxG(s)) end do !温度の効果 xz_EffPotTemp = xz_PotTemp / xz_PotTempBasicZ !分子量効果 + 引きづりの効果 xz_EffMolWt = & & + sum(xza_MixRtPerMolWt, 3) & & / ( 1.0d0 / MolWtDry + xz_MixRtBasicZPerMolWt ) & & - sum(xza_MixRt, 3) / ( 1.0d0 + xz_MixRtBasicZ ) !蒸気が蒸発する場合の潜熱を計算 ! 分子量の部分はいつでも効くが潜熱は飽和していないと効かないので, ! 雲の混合比がゼロの時には, 潜熱の寄与はゼロとなるように調節している xza_MixRtAll2 = xza_MixRtAll ! xza_MixRtAll2(:,:,IdxNH3) = xza_MixRtAll(:,:,IdxNH3) - xza_MixRtAll(:,:,IdxH2S) do s = 1, CondNum xza_LatentHeat(:,:,s) = & & xz_LatentHeat( SpcWetID(IdxCC(s)), xz_TempAll ) & & * xza_MixRtAll2(:,:,IdxCG(s)) & ! & * ( 5.0d-1 + sign( 5.0d-1, (xza_MixRtAll2(:,:,IdxCC(s)) - 1.0d-8) ) ) & * ( 5.0d-1 + sign( 5.0d-1, (xza_MixRtAll2(:,:,IdxCC(s)) - 1.0d-4) ) ) end do xz_EffHeat = ( sum( xza_LatentHeat, 3 ) * xz_EffMolWtBasicZ & ! & + ReactHeatNH4SH * (xza_MixRtAll(:,:,IdxH2S) + xza_MixRtAll(:,:,IdxH2S)) & & ) / ( CpDry * xz_ExnerBasicZ ) !乱流拡散係数の時間発展式の浮力項を決める xz_BuoyMoistKm = & & - 3.0d0 * Grav * ( Cm ** 2.0d0 ) * ( MixLen ** 2.0d0 ) & & * xz_avr_xr( & & xr_dz_xz( & & xz_EffHeat & & + xz_PotTempBasicZ / xz_EffMolWtBasicZ & & * ( 1.0d0 + xz_EffPotTemp + xz_EffMolWt ) & & ) & & ) & & / ( 2.0d0 * xz_PotTempBasicZ / xz_EffMolWtBasicZ) end function xz_BuoyMoistKm !!!------------------------------------------------------------------------!!! function xr_BuoyMolWt(xza_MixRt) ! ! 鉛直方向の運動方程式に現れる浮力項のうち, ! 分子量の効果だけを求める ! !暗黙の型宣言禁止 implicit none !変数定義 real(8), intent(in) :: xza_MixRt(DimXMin:DimXMax, DimZMin:DimZMax, SpcNum) !凝縮成分の混合比 real(8) :: xr_BuoyMolWt(DimXMin:DimXMax, DimZMin:DimZMax) !浮力項(分子量効果) real(8) :: xza_MixRtPerMolWt(DimXMin:DimXMax, DimZMin:DimZMax, GasNum) !混合比/分子量 integer :: s !初期化 xr_BuoyMolWt = 0.0d0 !作業配列の初期化. 気体のみ利用 do s = 1, GasNum xza_MixRtPerMolWt(:,:,s) = xza_MixRt(:,:,IdxG(s)) / MolWtWet(IdxG(s)) end do !浮力項の計算 xr_BuoyMolWt = & & + Grav * xr_avr_xz( sum(xza_MixRtPerMolWt, 3) ) & & / ( 1.0d0 / MolWtDry + xr_MixRtBasicZPerMolWt ) & & - Grav * xr_avr_xz( sum(xza_MixRt(:,:,1:GasNum), 3) ) & & / ( 1.0d0 + xr_MixRtBasicZ ) call StoreBuoyMolWt(xz_avr_xr(xr_BuoyMolWt)) end function xr_BuoyMolWt !!!------------------------------------------------------------------------!!! function xr_BuoyDrag(xza_MixRt) ! ! 鉛直方向の運動方程式に現れる浮力項のうち, ! 引きづりのの効果だけを求める ! !暗黙の型宣言禁止 implicit none !変数定義 real(8), intent(in) :: xza_MixRt(DimXMin:DimXMax, DimZMin:DimZMax, SpcNum) !凝縮成分の混合比 real(8) :: xr_BuoyDrag(DimXMin:DimXMax, DimZMin:DimZMax) !浮力項(分子量効果) !初期化 xr_BuoyDrag = 0.0d0 !浮力項の計算 xr_BuoyDrag = & & - Grav * xr_avr_xz( sum(xza_MixRt(:,:,GasNum+1:SpcNum), 3) ) & & / ( 1.0d0 + xr_MixRtBasicZ ) call StoreBuoyDrag(xz_avr_xr(xr_BuoyDrag)) end function xr_BuoyDrag end module MoistBuoyancy