number_surfaces Function

function number_surfaces(m_p, center, radius, get_dens) result(n_surfaces)

Uses

  • proc~~number_surfaces~~UsesGraph proc~number_surfaces number_surfaces constants constants proc~number_surfaces->constants module~utility utility proc~number_surfaces->module~utility module~utility->constants matrix matrix module~utility->matrix

Compute the number of surfaces by integrating the linear particle density along the larger equatorial radius

FT 22.07.2021


Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: m_p
double precision, intent(in) :: center
double precision, intent(in) :: radius
function get_dens(x, y, z) result(density)

Returns the baryon mass density at the desired point

Arguments
Type IntentOptional Attributes Name
double precision, intent(in) :: x

coordinate of the desired point

double precision, intent(in) :: y

coordinate of the desired point

double precision, intent(in) :: z

coordinate of the desired point

Return Value double precision

Return Value integer


Calls

proc~~number_surfaces~~CallsGraph proc~number_surfaces number_surfaces proc~is_finite_number is_finite_number proc~number_surfaces->proc~is_finite_number

Called by

proc~~number_surfaces~~CalledByGraph proc~number_surfaces number_surfaces proc~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces proc~place_particles_ellipsoidal_surfaces->proc~number_surfaces interface~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces interface~place_particles_ellipsoidal_surfaces->proc~place_particles_ellipsoidal_surfaces

Contents

Source Code


Variables

Type Visibility Attributes Name Initial
double precision, private :: n_surfaces_tmp
integer, private :: r
double precision, private :: rho_tmp
double precision, private :: x_tmp

Source Code

  FUNCTION number_surfaces( m_p, center, radius, get_dens ) &
           RESULT( n_surfaces )

    !************************************************
    !
    !# Compute the number of surfaces
    !  by integrating the linear particle density
    !  along the larger equatorial radius
    !
    !  FT 22.07.2021
    !
    !************************************************

    USE constants, ONLY: third
    USE utility,   ONLY: zero, is_finite_number

    IMPLICIT NONE

    DOUBLE PRECISION, INTENT( IN ):: m_p, center, radius
    INTERFACE
      FUNCTION get_dens( x, y, z ) RESULT( density )
        !! Returns the baryon mass density at the desired point
        DOUBLE PRECISION, INTENT(IN):: x
        !! \(x\) coordinate of the desired point
        DOUBLE PRECISION, INTENT(IN):: y
        !! \(y\) coordinate of the desired point
        DOUBLE PRECISION, INTENT(IN):: z
        !! \(z\) coordinate of the desired point
        DOUBLE PRECISION:: density
        !> Baryon mass density at \((x,y,z)\)
      END FUNCTION get_dens
    END INTERFACE


    INTEGER:: n_surfaces

    INTEGER:: r
    DOUBLE PRECISION:: n_surfaces_tmp, x_tmp, rho_tmp
  !  DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE:: particle_profile
  !
  !  IF(.NOT.ALLOCATED( particle_profile ))THEN
  !    ALLOCATE( particle_profile( 2, 500 ), STAT= ios, &
  !              ERRMSG= err_msg )
  !    IF( ios > 0 )THEN
  !       PRINT *, "...allocation error for array particle_profile in" &
  !                // "FUNCTION number_surfaces. ", &
  !                "The error message is", err_msg
  !       STOP
  !    ENDIF
  !  ENDIF

    n_surfaces_tmp= zero

    DO r= 1, 500, 1

      x_tmp  = center + r*radius/DBLE(500)
      rho_tmp= get_dens( x_tmp, zero, zero )

      IF( .NOT.is_finite_number(( rho_tmp/m_p )**third) )THEN
        CYCLE
      ENDIF

      n_surfaces_tmp= n_surfaces_tmp + &
                      radius/DBLE(500)*(( rho_tmp/m_p )**third)

    ENDDO

    IF( .NOT.is_finite_number(n_surfaces_tmp) )THEN
      PRINT *, "** ERROR in SUBROUTINE number_surfaces!", &
               " n_surfaces_tmp = ", n_surfaces_tmp, " is not a finite number!"
      PRINT *
      STOP
    ENDIF
    IF( n_surfaces_tmp <= zero )THEN
      PRINT *, "** ERROR in SUBROUTINE number_surfaces!", &
               " n_surfaces_tmp = ", n_surfaces_tmp, " is nonpositive!"
      PRINT *
      STOP
    ENDIF

    n_surfaces= NINT( n_surfaces_tmp )


  END FUNCTION number_surfaces