test_wd_eos_cgs Subroutine

public subroutine test_wd_eos_cgs(rho_input, rho, pr, u)

Test that the implementation is correct. Takes the density in code units as input, and assigns CGS values to the pressure, and the density recomputed from the pressure. It also computed the dimensionless specific internal energy.

FT 20.12.2022


Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: rho_input
double precision, intent(out) :: rho
double precision, intent(out) :: pr
double precision, intent(out) :: u

Calls

proc~~test_wd_eos_cgs~~CallsGraph proc~test_wd_eos_cgs test_wd_eos_cgs proc~pr_wd pr_wd proc~test_wd_eos_cgs->proc~pr_wd proc~rho_wd rho_wd proc~test_wd_eos_cgs->proc~rho_wd proc~u_wd u_wd proc~test_wd_eos_cgs->proc~u_wd proc~f_wd f_wd proc~pr_wd->proc~f_wd proc~rho_wd->proc~pr_wd proc~g_wd g_wd proc~u_wd->proc~g_wd proc~g_wd->proc~f_wd

Contents

Source Code


Source Code

  SUBROUTINE test_wd_eos_cgs(rho_input, rho, pr, u)

    !********************************************
    !
    !# Test that the implementation is correct.
    !  Takes the density in code units as input,
    !  and assigns CGS values to the pressure,
    !  and the density recomputed from the pressure.
    !  It also computed the dimensionless
    !  specific internal energy.
    !
    !  FT 20.12.2022
    !
    !********************************************

    IMPLICIT NONE

    DOUBLE PRECISION, INTENT(IN) :: rho_input
    DOUBLE PRECISION, INTENT(OUT):: rho, pr, u

    PRINT *, "** Testing that the implementation of the Chandrasekhar EOS", &
             " for white dwarfs is correct."
    PRINT *

    PRINT *, "   a_wd in code units=", a_wd
    PRINT *, "   b_wd in code units=", b_wd
    PRINT *, "   a_wd in CGS units=",  a_wd_cgs
    PRINT *, "   b_wd in CGS units=",  b_wd_cgs
    PRINT *
    PRINT *, "   rho_input in code units=", rho_input
    PRINT *, "   rho_input in CGS units=", &
             rho_input/dens_si2cu*kg2g/(m2cm**3)
    PRINT *

    pr = pr_wd(rho_input)
    u  = u_wd(rho_input)
    rho= rho_wd(pr,0.D0,1.D0)

    PRINT *, "   pr in code units=", pr
    pr= pr/dens_si2cu*kg2g/(m2cm**3)*c_light2
    PRINT *, "   pr in CGS units=", pr
    PRINT *

    PRINT *, "   u (dimensionless)=", u
    PRINT *

    PRINT *, "   Recomputed rho in code units=", rho
    rho= rho/dens_si2cu*kg2g/(m2cm**3)
    PRINT *, "   Recomputed rho in CGS units=", rho
    PRINT *

  END SUBROUTINE test_wd_eos_cgs