! $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 = .true., leos_chemistry = .false. ! ! MVAR 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; glnmumol(3); ppvap; csvap2 ! PENCILS PROVIDED TTb; rho_anel; eth; geth(3); del2eth; heth(3,3) ! PENCILS PROVIDED eths; geths(3); rho1gpp(3) ! !*************************************************************** module EquationOfState ! use Cdata use General, only: keep_compiler_quiet use Messages use DensityMethods, only: getlnrho,getrho,getrho_s use SharedVariables, only: get_shared_variable ! implicit none ! include 'eos.h' include 'eos_params.h' ! integer :: iglobal_cs2, iglobal_glnTT real :: lnTT0=impossible, TT0=impossible real :: xHe=0.0 real :: mu=1.0 real :: cs0=1.0, cs20=1.0, cs20t, rho0=1., lnrho0=0., rho01=1.0, pp0=1.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 :: cp=impossible, cp1=impossible, cv=impossible, cv1=impossible real :: pres_corr=0.1 real :: cs2bot=impossible, cs2top=impossible real :: fac_cs=1.0, cs20_tdep_rate=1.0 real, pointer :: mpoly real :: sigmaSBt=1.0 integer :: isothmid=0 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. logical :: lanelastic_lin=.false., lcs_as_aux=.false., lcs_as_comaux=.false. logical :: lcs_tdep=.false. ! character (len=labellen) :: meanfield_Beq_profile real, pointer :: meanfield_Beq, chit_quenching, uturb real, dimension(:), pointer :: B_ext ! real :: Cp_const=impossible real :: Pr_number=0.7 logical :: lpres_grad=.false. integer :: imass=0 ! ! Background stratification data ! character(len=labellen) :: gztype = 'zero' real :: gz_coeff = 0.0 ! ! Input parameters. ! namelist /eos_init_pars/ & xHe, mu, cp, cs0, rho0, gamma, error_cp, & sigmaSBt, lanelastic_lin, lcs_as_aux, lcs_as_comaux,& fac_cs,isothmid, lstratz, gztype, gz_coeff, lpres_grad, & lcs_tdep, cs20_tdep_rate ! ! Run parameters. ! namelist /eos_run_pars/ & xHe, mu, cp, cs0, rho0, gamma, error_cp, & pres_corr, sigmaSBt, & lanelastic_lin, lcs_as_aux, lcs_as_comaux, & lcs_tdep, cs20_tdep_rate ! ! Module variables ! real, dimension(mz) :: rho0z = 0.0 real, dimension(mz) :: dlnrho0dz = 0.0 real, dimension(mz) :: eth0z = 0.0 logical :: lstratset = .false. integer, parameter :: XBOT=1, XTOP=nx real, dimension(:,:), pointer :: reference_state ! contains !*********************************************************************** subroutine register_eos ! ! Register variables from the EquationOfState module. ! ! 14-jun-03/axel: adapted from register_eos ! use SharedVariables, only: put_shared_variable ! if ((ip<=8) .and. lroot) print*, 'register_eos: ionization nvar = ', nvar ! ! Identify version number. ! if (lroot) call svn_id( & '$Id$') ! ! Shared variables ! call put_shared_variable('cs20',cs20,caller='register_eos') call put_shared_variable('gamma',gamma) call put_shared_variable('cp',cp) call put_shared_variable('cv',cv) call put_shared_variable('isothmid',isothmid) call put_shared_variable('fac_cs',fac_cs) ! if (.not.ldensity) then call put_shared_variable('rho0',rho0) call put_shared_variable('lnrho0',lnrho0) endif ! if (lanelastic) call put_shared_variable('lanelastic_lin',lanelastic_lin) ! 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 ! 4-aug-09/axel: added possibility of vertical profile function ! use Sub, only: erfunc ! real :: Rgas_unit_sys, cp_reference ! ! Set gamma_m1, cs20, and lnrho0, and rho01. ! (used currently for non-dimensional equation of state) ! gamma_m1=gamma-1.0 gamma1=1/gamma lnrho0=log(rho0) rho01 = 1./rho0 ! ! Avoid floating overflow if cs0 was not set. ! cs20=cs0**2 ! ! 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 elseif (unit_system=='set') then if (gamma_m1==0.0) then Rgas_unit_sys=mu*cp_set else Rgas_unit_sys=mu*gamma_m1*gamma1*cp_set endif endif ! if (unit_temperature==impossible) then if (lfix_unit_std) then !Fred: sets optimal unit temperature lnTT0=0 Rgas=mu*gamma1 if (cp==impossible) then if (gamma_m1==0.0) then cp=Rgas/mu else cp=Rgas/(mu*gamma_m1*gamma1) endif endif unit_temperature=unit_velocity**2*Rgas/Rgas_unit_sys else if (cp==impossible) cp=cp_set if (gamma_m1==0.0) then Rgas=mu*cp else Rgas=mu*(1.0-gamma1)*cp endif unit_temperature=unit_velocity**2*Rgas/Rgas_unit_sys endif else Rgas=Rgas_unit_sys*unit_temperature/unit_velocity**2 if (cp==impossible) then if (gamma_m1==0.0) then cp=Rgas/mu else cp=Rgas/(mu*gamma_m1*gamma1) endif else ! ! Checking whether the units are overdetermined. ! This is assumed to be the case when the two differ by error_cp. ! if (gamma_m1==0.0) then cp_reference=Rgas/mu else cp_reference=Rgas/(mu*gamma_m1*gamma1) endif ! ! Check against reference. ! if (abs(cp-cp_reference)/cp > error_cp) then if (lroot) print*,'Rgas,mu=', Rgas, mu if (lroot) print*,'units_eos: consistency: cp=',cp, 'while: cp_reference=', cp_reference if (lroot) print*,'also caused when changing gamma btw start/run!' call fatal_error('units_eos','cp is not correctly calculated') endif endif endif cp1=1/cp cv=gamma1*cp cv1=gamma*cp1 ! ! Need to calculate the equivalent of cs0. ! Distinguish between gamma=1 case and not. ! if (gamma_m1/=0.0) then lnTT0=log(cs20/(cp*gamma_m1)) !(general case) else lnTT0=log(cs20/cp) !(isothermal/polytropic cases: check!) endif pp0=Rgas*exp(lnTT0)*rho0 TT0=exp(lnTT0) ! ! Check that everything is OK. ! if (lroot) then print*, 'units_eos: unit_temperature=', unit_temperature print*, 'units_eos: cp, lnTT0, cs0, pp0, Rgas=', cp, lnTT0, cs0, pp0, Rgas endif ! endsubroutine units_eos !*********************************************************************** subroutine initialize_eos(f) ! use FArrayManager use SharedVariables, only: get_shared_variable use Sub, only: register_report_aux ! real, dimension (mx,my,mz,mfarray) :: f ! ! Perform any post-parameter-read initialization ! ! 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,*) 'cp=',cp close (1) endif ! ! cs as optional auxiliary variable ! if (lcs_as_aux .or. lcs_as_comaux) call register_report_aux('cs',ics,communicated=lcs_as_comaux) ! ! Set background stratification, if any. ! if (lstratz) call set_stratz lstratset = .true. ! if (lfargo_advection.and.(pretend_lnTT.or.ltemperature)) & call not_implemented("initialize_eos","fargo advection for temperature equation") ! if (lreference_state) call get_shared_variable('reference_state',reference_state, & caller='initialize_eos') ! ! Register gradient of pressure ! if (lpres_grad) then call farray_register_auxiliary('gpx',igpx) ! ! Writing files for use with IDL ! aux_count = aux_count+1 ! call farray_register_auxiliary('gpy',igpy) ! ! Writing files for use with IDL ! aux_count = aux_count+1 endif ! if (lentropy.and.gamma_m1==0.) call warning('initialize_eos','gamma=1 not allowed w/entropy') if (gamma_m1==0.and..not.lanelastic) call warning('initialize_eos','gamma=1 not allowed w/entropy') ! endsubroutine initialize_eos !*********************************************************************** subroutine select_eos_variable(variable,findex) ! ! Select eos variable. ! ! 02-apr-06/tony: implemented ! use FArrayManager, only: farray_register_global use General, only: itoa ! character (len=*), intent(in) :: variable integer, intent(in) :: findex integer :: this_var=-1 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 integer, parameter :: ieosvar_eth = 2**7 ! if (ieosvar_count==0) ieosvar_selected=0 ! if (ieosvar_count>=2) call fatal_error('select_eos_variable', & 'two thermodynamic quantities already defined while attempting to add a 3rd') ! ieosvar_count=ieosvar_count+1 ! 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. elseif (variable=='eth') then this_var=ieosvar_eth 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