particle_volume Function

function particle_volume(rad, col, dr_shells, dth_shells, dphi_shells, th, colatitudes, npart_equator) result(pvol)

Uses

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

Compute the geometrical particle volume not the proper particle volume.

FT 23.07.2021


Arguments

Type IntentOptional Attributes Name
double precision, intent(in) :: rad
double precision, intent(in) :: col
double precision, intent(in) :: dr_shells
double precision, intent(inout) :: dth_shells
double precision, intent(in) :: dphi_shells
integer, intent(in) :: th
double precision, intent(in), DIMENSION(:) :: colatitudes
integer, intent(in) :: npart_equator

Return Value double precision


Called by

proc~~particle_volume~~CalledByGraph proc~particle_volume particle_volume proc~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces proc~place_particles_ellipsoidal_surfaces->proc~particle_volume interface~place_particles_ellipsoidal_surfaces place_particles_ellipsoidal_surfaces interface~place_particles_ellipsoidal_surfaces->proc~place_particles_ellipsoidal_surfaces

Contents

Source Code


Source Code

  FUNCTION particle_volume( rad, col, dr_shells, dth_shells, dphi_shells, th, &
                            colatitudes, npart_equator ) RESULT( pvol )

    !*******************************************
    !
    !# Compute the geometrical particle volume
    !  not the proper particle volume.
    !
    !  FT 23.07.2021
    !
    !*******************************************

    USE constants,  ONLY: pi
    USE utility,    ONLY: two

    IMPLICIT NONE

    INTEGER,          INTENT( IN ):: th, npart_equator
    DOUBLE PRECISION, INTENT( IN ):: rad, col, dr_shells, dphi_shells
    DOUBLE PRECISION, INTENT( IN OUT ):: dth_shells
    DOUBLE PRECISION, DIMENSION(:), INTENT( IN ):: colatitudes

    DOUBLE PRECISION:: pvol

    IF( th == 1 )THEN

    !dth_shells= pi - ( col + colatitude_pos(r)% colatitudes(th+1) )/two
      IF( npart_equator == 4 )THEN

        dth_shells= pi

      ELSE

        dth_shells= two*ABS( col - &
                ( col + colatitudes(th + 1) )/two )
      ENDIF

    ELSEIF( th == npart_equator/4 )THEN

    !dth_shells= ( colatitude_pos(r)% colatitudes(th-1) + col - pi )/two
      dth_shells= two*ABS( ( colatitudes(th - 1) &
                + col )/two - col )

    ELSE

      dth_shells= ABS( &
              ( colatitudes(th + 1) + col )/two &
            - ( col + colatitudes(th - 1) )/two )

    ENDIF

    pvol= rad**two*SIN(col)*dr_shells*dth_shells*dphi_shells! &

  END FUNCTION particle_volume