! $Id: eos_idealgas_vapor.f90,v 1.7 2010/02/03 10:30:37 ajohan Exp $ ! ! Equation of state for an ideal gas with variable water vapour. ! !** AUTOMATIC CPARAM.INC GENERATION **************************** ! Declare (for generation of cparam.inc) the number of f array ! variables and auxiliary variables added by this module ! ! CPARAM logical, parameter :: leos = .true. ! ! MVAR CONTRIBUTION 0 ! MAUX CONTRIBUTION 0 ! ! PENCILS PROVIDED ss; gss(3); ee; pp; lnTT; cs2; cp; cp1; cp1tilde ! PENCILS PROVIDED glnTT(3); TT; TT1; gTT(3); yH; hss(3,3); hlnTT(3,3) ! PENCILS PROVIDED del2ss; del6ss; del2lnTT; cv; cv1; del6lnTT; gamma ! PENCILS PROVIDED del2TT; del6TT; mumol; mumol1; glnmumol(3) ! PENCILS PROVIDED rho_anel; ppvap; csvap2 ! !*************************************************************** module EquationOfState ! use Cparam use Cdata use General, only: keep_compiler_quiet use Messages ! implicit none ! include '../eos.h' ! integer, parameter :: ilnrho_ss=1, ilnrho_ee=2, ilnrho_pp=3 integer, parameter :: ilnrho_lnTT=4, ilnrho_cs2=5 integer, parameter :: irho_cs2=6, irho_ss=7, irho_lnTT=8, ilnrho_TT=9 integer, parameter :: irho_TT=10, ipp_ss=11, ipp_cs2=12 integer, parameter :: irho_eth=13, ilnrho_eth=14 integer :: iglobal_cs2, iglobal_glnTT, ics real, dimension(nchemspec,18) :: species_constants real :: Rgas_unit_sys=1.0 real :: lnTT0=impossible real :: mudry=1.0, muvap=1.0, mudry1=1.0, muvap1=1.0 real :: cs0=1.0, rho0=1.0, pp0=1.0 real :: cs20=1.0, lnrho0=0.0 real :: ptlaw=0.0 real :: gamma=5.0/3.0 real :: Rgas_cgs=0.0, Rgas, error_cp=1.0e-6 real :: gamma_m1 !(=gamma-1) real :: gamma1 !(=1/gamma) real :: cpdry=impossible, cpdry1=impossible real :: cvdry=impossible, cvdry1=impossible real :: cs2bot=1.0, cs2top=1.0 integer :: imass=1 integer :: ieosvars=-1, ieosvar1=-1, ieosvar2=-1, ieosvar_count=0 logical :: leos_isothermal=.false., leos_isentropic=.false. logical :: leos_isochoric=.false., leos_isobaric=.false. logical :: leos_localisothermal=.false. ! ! Input parameters. ! namelist /eos_init_pars/ & mudry, muvap, cpdry, cs0, rho0, gamma, error_cp, ptlaw ! ! Run parameters. ! namelist /eos_run_pars/ & mudry, muvap, cpdry, cs0, rho0, gamma, error_cp, ptlaw ! contains !*********************************************************************** subroutine register_eos() ! ! Register variables from the EquationOfState module. ! ! 06-jan-10/anders: adapted from eos_idealgas ! leos_idealgas=.true. ! iyH=0 ilnTT=0 ! if ((ip<=8) .and. lroot) then print*, 'register_eos: ionization nvar = ', nvar endif ! ! Identify version number. ! if (lroot) call svn_id( & '$Id: eos_idealgas_vapor.f90,v 1.7 2010/02/03 10:30:37 ajohan Exp $') ! endsubroutine register_eos !*********************************************************************** subroutine units_eos() ! ! This routine calculates things related to units and must be called ! before the rest of the units are being calculated. ! ! 06-jan-10/anders: adapted from eos_idealgas ! real :: cp_reference ! ! Set gamma_m1, cs20, and lnrho0 ! (used currently for non-dimensional equation of state) ! gamma_m1=gamma-1.0 gamma1=1/gamma ! ! Avoid floating overflow if cs0 was not set. ! cs20=cs0**2 lnrho0=log(rho0) ! ! Initialize variable selection code (needed for RELOADing). ! ieosvars=-1 ieosvar_count=0 ! ! Unless unit_temperature is set, calculate by default with cp=1. ! If unit_temperature is set, cp must follow from this. ! Conversely, if cp is set, then unit_temperature must follow from this. ! If unit_temperature and cp are set, the problem is overdetermined, ! but it may still be correct, so this will be checked here. ! When gamma=1.0 (gamma_m1=0.0), write Rgas=mu*cp or cp=Rgas/mu. ! if (unit_system=='cgs') then Rgas_unit_sys=k_B_cgs/m_u_cgs elseif (unit_system=='SI') then Rgas_unit_sys=k_B_cgs/m_u_cgs*1.0e-4 endif ! if (unit_temperature==impossible) then if (cpdry==impossible) cpdry=1.0 if (gamma_m1==0.0) then Rgas=mudry*cpdry else Rgas=mudry*(1.0-gamma1)*cpdry endif unit_temperature=unit_velocity**2*Rgas/Rgas_unit_sys else Rgas=Rgas_unit_sys*unit_temperature/unit_velocity**2 if (cpdry==impossible) then if (gamma_m1==0.0) then cpdry=Rgas/mudry else cpdry=Rgas/(mudry*gamma_m1*gamma1) if (headt) print*,'units_eos: cpdry=',cpdry endif else ! ! Checking whether the units are overdetermined. ! This is assumed to be the case when the to differ by error_cp. ! if (gamma_m1==0.0) then cp_reference=Rgas/mudry else cp_reference=Rgas/(mudry*gamma_m1*gamma1) endif if (abs(cpdry-cp_reference)/cpdry > error_cp) then if (lroot) print*,'initialize_eos: consistency: cpdry=', cpdry , & 'while: cp_reference=', cp_reference call fatal_error('initialize_eos','') endif endif endif cpdry1=1/cpdry cvdry=gamma1*cpdry cvdry1=gamma*cpdry1 ! ! Need to calculate the equivalent of cs0. ! Distinguish between gamma=1 case and not. ! if (gamma_m1/=0.0) then lnTT0=log(cs20/(cpdry*gamma_m1)) !(general case) else lnTT0=log(cs20/cpdry) !(isothermal/polytropic cases: check!) endif lnTT0=0.0 pp0=Rgas*exp(lnTT0)*rho0 ! ! Check that everything is OK. ! if (lroot) then print*, 'initialize_eos: unit_temperature=', unit_temperature print*, 'initialize_eos: cpdry, lnTT0, cs0, pp0=', & cpdry, lnTT0, cs0, pp0 endif ! endsubroutine units_eos !*********************************************************************** subroutine initialize_eos() ! ! Perform any post-parameter-read initialization ! ! 06-jan-10/anders: adapted from eos_idealgas ! mudry1=1/mudry muvap1=1/muvap ! ! Initialize variable selection code (needed for RELOADing). ! ieosvars=-1 ieosvar_count=0 ! ! Write constants to disk. In future we may want to deal with this ! using an include file or another module. ! if (lroot) then open (1,file=trim(datadir)//'/pc_constants.pro',position="append") write (1,'(a,1pd26.16)') 'k_B=', k_B write (1,'(a,1pd26.16)') 'm_H=', m_H write (1,*) 'lnrho0=', lnrho0 write (1,*) 'lnTTO=', lnTT0 write (1,*) 'cs20=', cs20 write (1,*) 'cpdry=', cpdry close (1) endif ! endsubroutine initialize_eos !*********************************************************************** subroutine select_eos_variable(variable,findex) ! ! Select eos variable. ! ! 06-jan-10/anders: adapted from eos_idealgas ! use FArrayManager ! character (len=*), intent(in) :: variable integer, intent(in) :: findex integer :: this_var integer, save :: ieosvar_selected=0 integer, parameter :: ieosvar_lnrho = 2**0 integer, parameter :: ieosvar_rho = 2**1 integer, parameter :: ieosvar_ss = 2**2 integer, parameter :: ieosvar_lnTT = 2**3 integer, parameter :: ieosvar_TT = 2**4 integer, parameter :: ieosvar_cs2 = 2**5 integer, parameter :: ieosvar_pp = 2**6 ! if (ieosvar_count==0) ieosvar_selected=0 ! if (ieosvar_count>=2) & call fatal_error('select_eos_variable', & '2 thermodynamic quantities have already been defined '// & 'while attempting to add a 3rd') ! ieosvar_count=ieosvar_count+1 ! if (variable=='ss') then this_var=ieosvar_ss if (findex<0) then leos_isentropic=.true. endif elseif (variable=='cs2') then this_var=ieosvar_cs2 if (findex==-2) then leos_localisothermal=.true. call farray_register_global('cs2',iglobal_cs2) call farray_register_global('glnTT',iglobal_glnTT,vector=3) elseif (findex<0) then leos_isothermal=.true. endif elseif (variable=='lnTT') then this_var=ieosvar_lnTT if (findex<0) then leos_isothermal=.true. endif elseif (variable=='TT') then this_var=ieosvar_TT elseif (variable=='lnrho') then this_var=ieosvar_lnrho if (findex<0) then leos_isochoric=.true. endif elseif (variable=='rho') then this_var=ieosvar_rho if (findex<0) then leos_isochoric=.true. endif elseif (variable=='pp') then this_var=ieosvar_pp if (findex<0) then leos_isobaric=.true. endif else call fatal_error('select_eos_variable','unknown thermodynamic variable') endif if (ieosvar_count==1) then ieosvar1=findex ieosvar_selected=ieosvar_selected+this_var return endif ! ! Ensure the indexes are in the correct order. ! if (this_var