! $Id$ ! ! Thermodynamics with Fixed ionization fraction ! ! !** 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 rho_anel ! PENCILS PROVIDED del2ss; del6ss; del2lnTT; cv; cv1; glnmumol(3); ppvap; csvap2 ! PENCILS PROVIDED rho1gpp(3) ! !*************************************************************** module EquationOfState ! use Cparam use Cdata use General, only: keep_compiler_quiet use Messages use Mpicomm, only: stop_it ! implicit none ! include 'eos.h' ! ! integers specifying which independent variables to use in eoscalc ! (only relevant in ionization.f90) integer, parameter :: ilnrho_ss=1,ilnrho_ee=2,ilnrho_pp=3,ilnrho_lnTT=4 integer, parameter :: irho_ss=7, ilnrho_TT=9, irho_TT=10, ipp_ss=11 integer, parameter :: ipp_cs2=12 integer, parameter :: irho_eth=13, ilnrho_eth=14 ! Constants use in calculation of thermodynamic quantities real :: lnTTss,lnTTlnrho,lnTT0 ! ! secondary parameters calculated in initialize real :: TT_ion,lnTT_ion,TT_ion_,lnTT_ion_ real :: ss_ion,ee_ion,kappa0,Srad0 real :: lnrho_H,lnrho_e,lnrho_e_,lnrho_p,lnrho_He real :: xHe_term,yH_term,one_yH_term ! real :: yH0=.0,xHe=0.1,xH2=0.,kappa_cst=1. character (len=labellen) :: opacity_type='ionized_H' ! namelist /eos_init_pars/ yH0,xHe,xH2,opacity_type,kappa_cst ! namelist /eos_run_pars/ yH0,xHe,xH2,opacity_type,kappa_cst !ajwm can't use impossible else it breaks reading param.nml !ajwm SHOULDN'T BE HERE... But can wait till fully unwrapped real :: cs0=1., rho0=1., cp=1. real :: cs20=1., lnrho0=0. logical :: lcalc_cp = .false. real :: gamma=5./3., gamma_m1,gamma1, nabla_ad !real :: cp=impossible, cp1=impossible real :: cp1=impossible,cv=impossible !ajwm can't use impossible else it breaks reading param.nml real :: cs2bot=1., cs2top=1. integer :: imass=1, ics ! real, dimension(nchemspec,18) :: species_constants ! real :: Cp_const=impossible real :: Pr_number=0.7 logical :: lpres_grad = .false. ! contains !*********************************************************************** subroutine register_eos ! ! 14-jun-03/axel: adapted from register_ionization ! use Sub ! leos_fixed_ionization=.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$") ! endsubroutine register_eos !******************************************************************* subroutine getmu(f,mu_tmp) ! ! Calculate mean molecular weight of the gas ! ! 12-aug-03/tony: implemented ! 30-mar-04/anders: Added molecular hydrogen to ionization_fixed ! real, dimension (mx,my,mz,mfarray), optional :: f real, optional, intent(out) :: mu_tmp ! mu_tmp = (1.+3.97153*xHe)/(1-xH2+xHe) ! ! Complain if xH2 not between 0 and 0.5 ! if (xH2 < 0. .or. xH2 > 0.5) & call stop_it('initialize_ionization: xH2 must be <= 0.5 and >= 0.0') ! call keep_compiler_quiet(present(f)) ! endsubroutine getmu !*********************************************************************** subroutine units_eos ! ! dummy: here we don't allow for inputting cp. ! endsubroutine units_eos !*********************************************************************** subroutine initialize_eos ! ! Perform any post-parameter-read initialization, e.g. set derived ! parameters. ! ! 2-feb-03/axel: adapted from Interstellar module ! use SharedVariables, only: put_shared_variable ! integer :: ierr real :: mu1yHxHe ! ! ionization parameters ! since m_e and chiH, as well as hbar are all very small ! it is better to divide m_e and chiH separately by hbar. ! if (headtt) print*,'initialize_eos: assume cp is not 1, yH0=',yH0 mu1yHxHe=1.+3.97153*xHe TT_ion=chiH/k_B lnTT_ion=log(chiH/k_B) TT_ion_=chiH_/k_B lnTT_ion_=log(chiH_/k_B) lnrho_e=1.5*log((m_e/hbar)*(chiH/hbar)/2./pi)+log(m_H)+log(mu1yHxHe) lnrho_H=1.5*log((m_H/hbar)*(chiH/hbar)/2./pi)+log(m_H)+log(mu1yHxHe) lnrho_p=1.5*log((m_p/hbar)*(chiH/hbar)/2./pi)+log(m_H)+log(mu1yHxHe) lnrho_He=1.5*log((m_He/hbar)*(chiH/hbar)/2./pi)+log(m_H)+log(mu1yHxHe) lnrho_e_=1.5*log((m_e/hbar)*(chiH_/hbar)/2./pi)+log(m_H)+log(mu1yHxHe) ss_ion=k_B/m_H/mu1yHxHe ee_ion=ss_ion*TT_ion gamma_m1=gamma-1. gamma1=1./gamma nabla_ad=gamma_m1/gamma kappa0=sigmaH_/m_H/mu1yHxHe/4.0 Srad0=sigmaSB*TT_ion**4.0D0/pi ! if (lroot) then print*,'initialize_eos: reference values for ionization' print*,'initialize_eos: TT_ion,lnrho_e,ss_ion=',TT_ion,lnrho_e,ss_ion endif ! if (yH0>0.) then yH_term=yH0*(2*log(yH0)-lnrho_e-lnrho_p) elseif (yH0<0.) then call stop_it('initialize_eos: yH0 must not be lower than zero') else yH_term=0. endif ! if (yH0<1.) then one_yH_term=(1.-yH0)*(log(1.-yH0)-lnrho_H) elseif (yH0>1.) then call stop_it('initialize_eos: yH0 must not be greater than one') else one_yH_term=0. endif ! if (xHe>0.) then xHe_term=xHe*(log(xHe)-lnrho_He) elseif (xHe<0.) then call stop_it('initialize_eos: xHe lower than zero makes no sense') else xHe_term=0. endif ! ! Set the reference sound speed (used for noionisation to impossible) ! lnTTss=(2./3.)/(1.+yH0+xHe-xH2)/ss_ion lnTTlnrho=2./3. ! lnTT0=lnTT_ion+(2./3.)*((yH_term+one_yH_term+xHe_term)/ & (1+yH0+xHe-xH2)-2.5) if (.not.ldensity) then call put_shared_variable('rho0',rho0,caller='initialize_eos') call put_shared_variable('lnrho0',lnrho0) endif ! if (lroot) then print*,'initialize_eos: reference values for ionization' print*,'initialize_eos: TT_ion,ss_ion,kappa0=', & TT_ion,ss_ion,kappa0 print*,'initialize_eos: lnrho_e,lnrho_H,lnrho_p,lnrho_He,lnrho_e_=', & lnrho_e,lnrho_H,lnrho_p,lnrho_He,lnrho_e_ endif ! ! write scale non-free constants to file; to be read by idl ! if (lroot) then open (1,file=trim(datadir)//'/pc_constants.pro',position="append") write (1,*) 'TT_ion=',TT_ion write (1,*) 'TT_ion_=',TT_ion_ write (1,*) 'lnrho_e=',lnrho_e write (1,*) 'lnrho_H=',lnrho_H write (1,*) 'lnrho_p=',lnrho_p write (1,*) 'lnrho_He=',lnrho_He write (1,*) 'lnrho_e_=',lnrho_e_ write (1,*) 'ss_ion=',ss_ion write (1,*) 'ee_ion=',ee_ion write (1,*) 'kappa0=',kappa0 write (1,*) 'Srad0=',Srad0 write (1,*) 'lnTTss=',lnTTss write (1,*) 'lnTTlnrho=',lnTTlnrho write (1,*) 'lnTT0=',lnTT0 close (1) endif ! endsubroutine initialize_eos !******************************************************************* subroutine select_eos_variable(variable,findex) ! ! Calculate average particle mass in the gas relative to ! ! 02-apr-06/tony: implemented ! character (len=*), intent(in) :: variable integer, intent(in) :: findex ! call keep_compiler_quiet(variable) call keep_compiler_quiet(findex) ! DUMMY ideagas version below !! integer :: this_var=0 !! integer, save :: ieosvar=0 !! integer, save :: ieosvar_selected=0 !! integer, parameter :: ieosvar_lnrho = 1 !! integer, parameter :: ieosvar_rho = 2 !! integer, parameter :: ieosvar_ss = 4 !! integer, parameter :: ieosvar_lnTT = 8 !! integer, parameter :: ieosvar_TT = 16 !! integer, parameter :: ieosvar_cs2 = 32 !! integer, parameter :: ieosvar_pp = 64 !!! !! if (ieosvar>=2) & !! call fatal_error("select_eos_variable", & !! "2 thermodynamic quantities have already been defined while attempting to add a 3rd: ") !//variable) !! !! ieosvar=ieosvar+1 !! !!! select case (variable) !! 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. !! 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=='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==1) then !! ieosvar1=findex !! ieosvar_selected=ieosvar_selected+this_var !! return !! endif !!! !!! Ensure the indexes are in the correct order. !!! !! if (this_var