! $Id$ ! ! Equation of state for an ideal gas without ionization. ! !** 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., leos_ionization=.false., leos_temperature_ionization=.false. ! CPARAM logical, parameter :: leos_idealgas = .false., leos_chemistry = .true. ! ! MVAR CONTRIBUTION 0 ! MAUX CONTRIBUTION 0 ! ! PENCILS PROVIDED lnTT; glnTT(3); TT; TT1; gTT(3) ! PENCILS PROVIDED mu1; pp; del2pp; glnmu(3) ! PENCILS PROVIDED rho1gpp(3); glnpp(3); del2lnTT ! PENCILS PROVIDED glnRR(3), RRmix ! ! PENCILS PROVIDED hss(3,3); hlnTT(3,3); del2ss; del6ss; del6lnTT ! PENCILS PROVIDED yH; ee; ss; delta; glnmumol(3); ppvap; csvap2; cs2 ! PENCILS PROVIDED cp1tilde; cp; gamma; gamma_m1 ! PENCILS PROVIDED rho_anel; gradcp(3) ! ! !*************************************************************** module EquationOfState ! use Cdata use General, only: keep_compiler_quiet use Messages ! implicit none ! include 'eos.h' include 'eos_params.h' ! integer :: iglobal_cs2, iglobal_glnTT ! real :: mu=1. real :: cs0=1., rho0=1. real :: cs20=1., lnrho0=0. real :: gamma=impossible real :: Rgas_cgs=0., Rgas, Rgas_unit_sys=1., error_cp=1e-6, scale_Rgas=1. real :: cp=impossible real :: cs2bot=1., cs2top=1. real :: lnTT0=impossible, TT0=impossible integer :: ieosvars=-1, ieosvar1=-1, ieosvar2=-1, ieosvar_count=0 integer :: ll1,ll2,mm1,mm2,nn1,nn2 logical :: leos_isothermal=.false., leos_isentropic=.false. logical :: leos_isochoric=.false., leos_isobaric=.false. logical :: leos_localisothermal=.false. character (len=20) :: input_file logical :: lcheminp_eos=.false. integer :: imass=1!, iTemp1=2,iTemp2=3,iTemp3=4 real :: Cp_const=impossible real :: Pr_number=0.7 logical :: lpres_grad = .false. logical :: linterp_pressure=.false. !This is only used when ogrid to interpolate pressure instead of temperature ! real, dimension(:,:), pointer :: species_constants ! namelist /eos_init_pars/ mu, cp, cs0, rho0, gamma, error_cp, Cp_const, lpres_grad, linterp_pressure, scale_Rgas ! namelist /eos_run_pars/ mu, cs0, rho0, Cp_const, Pr_number ! contains !*********************************************************************** subroutine register_eos ! ! 14-jun-03/axel: adapted from register_eos ! use FArrayManager use SharedVariables, only: put_shared_variable ! ilnTT = 0 ! if (lpres_grad) then ! ! Register gradient of pressure ! call farray_register_auxiliary('gpx',igpx) call farray_register_auxiliary('gpy',igpy) ! endif ! if (linterp_pressure) call farray_register_auxiliary('pp',ipp) ! ! Identify version number. ! if (lroot) call svn_id( & '$Id$') ! call put_shared_variable('gamma',gamma,caller='register_eos') call put_shared_variable('linterp_pressure',linterp_pressure) call put_shared_variable('scale_Rgas',scale_Rgas) 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. ! ! 22-jun-06/axel: adapted from initialize_eos ! 16-mar-10/Natalia ! logical :: chemin=.false.,cheminp=.false. ! ! Initialize variable selection code (needed for RELOADing) ! ieosvars=-1 ieosvar_count=0 ! 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.e-4 endif ! if (unit_temperature == impossible) then call fatal_error('units_eos','unit_temperature is not found') else Rgas=Rgas_unit_sys*unit_temperature*scale_Rgas/unit_velocity**2 endif ! inquire(file='chem.inp',exist=cheminp) inquire(file='chem.in',exist=chemin) if (chemin .and. cheminp) & call fatal_error('units_eos','chem.inp and chem.in found. Please decide for one') ! if (cheminp) input_file='chem.inp' if (chemin) input_file='chem.in' lcheminp_eos = cheminp .or. chemin ! endsubroutine units_eos !*********************************************************************** subroutine initialize_eos(f) ! ! Initialize variable selection code (needed for RELOADing) ! use SharedVariables, only: get_shared_variable ! real, dimension (mx,my,mz,mfarray) :: f 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 (pretend_lnTT) then call warning('initialize_eos','pretend_lnTT is not used with eos_chemistry_simple') pretend_lnTT=.false. endif 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,*) 'lnTTO=',lnTT0 write (1,*) 'cp=',cp close (1) endif ! if ((nxgrid==1) .and. (nygrid==1) .and. (nzgrid==1)) then ll1=1; ll2=mx; mm1=m1; mm2=m2; nn1=n1; nn2=n2 elseif (nxgrid==1) then ll1=l1; ll2=l2 else ll1=1; ll2=mx endif ! if (nygrid==1) then mm1=m1; mm2=m2 else mm1=1; mm2=my endif ! if (nzgrid==1) then nn1=n1; nn2=n2 else nn1=1; nn2=mz endif ! call get_shared_variable('species_constants',species_constants,caller='initialize_eos') ! endsubroutine initialize_eos !*********************************************************************** subroutine select_eos_variable(variable,findex) ! ! Select eos variable ! ! 02-apr-06/tony: implemented ! use FArrayManager use General, only: itoa ! character (len=*), intent(in) :: variable integer, intent(in) :: findex integer :: this_var=0 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") !//variable) ! ieosvar_count=ieosvar_count+1 ! ! select case (variable) if (variable=='ss') then this_var=ieosvar_ss if (findex<0) leos_isentropic=.true. 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) leos_isothermal=.true. elseif (variable=='TT') then this_var=ieosvar_TT elseif (variable=='lnrho') then this_var=ieosvar_lnrho if (findex<0) leos_isochoric=.true. elseif (variable=='rho') then this_var=ieosvar_rho if (findex<0) leos_isochoric=.true. elseif (variable=='pp') then this_var=ieosvar_pp if (findex<0) leos_isobaric=.true. else call fatal_error("select_eos_variable","no such thermodynamic variable: "//trim(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