geopotential_module Module

Gravity models for computing gravitational acceleration due to geopotential.

Each routine returns the acceleration in the body-fixed frame.

Example

    type(geopotential_model_mueller),target :: g
    call g%initialize(gravfile,n,m,status_ok)
    call g%get_acc(rvec,n,m,acc)

Note

Need to update to make sure they all work when N /= M


Uses

  • module~~geopotential_module~~UsesGraph module~geopotential_module geopotential_module module~kind_module kind_module module~geopotential_module->module~kind_module module~numbers_module numbers_module module~geopotential_module->module~numbers_module iso_fortran_env iso_fortran_env module~kind_module->iso_fortran_env module~numbers_module->module~kind_module

Used by

  • module~~geopotential_module~~UsedByGraph module~geopotential_module geopotential_module module~c_interface_module c_interface_module module~c_interface_module->module~geopotential_module module~fortran_astrodynamics_toolkit fortran_astrodynamics_toolkit module~fortran_astrodynamics_toolkit->module~geopotential_module module~fortran_astrodynamics_toolkit->module~c_interface_module

Abstract Interfaces

abstract interface

  • private subroutine acc_function(me, r, n, m, a)

    Interface to the acceleration function for the different methods

    Arguments

    Type IntentOptional Attributes Name
    class(geopotential_model), intent(inout) :: me
    real(kind=wp), intent(in), dimension(3) :: r
    integer, intent(in) :: n
    integer, intent(in) :: m
    real(kind=wp), intent(out), dimension(3) :: a

Derived Types

type, public ::  geopotential_model

The base abstract class for the various geopotential models

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure(acc_function), public, deferred :: get_acc

The models where the C,S coefficients are stored in vectors

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

real(kind=wp), public, dimension(:), allocatable :: c
real(kind=wp), public, dimension(:), allocatable :: s

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure(acc_function), public, deferred :: get_acc

The models where the C,S coefficients are stored in matrices

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

real(kind=wp), public, dimension(:,:), allocatable :: cnm
real(kind=wp), public, dimension(:,:), allocatable :: snm

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure(acc_function), public, deferred :: get_acc

Mueller method

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

real(kind=wp), public, dimension(:), allocatable :: c
real(kind=wp), public, dimension(:), allocatable :: s

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure, public :: get_acc => compute_gravity_acceleration_mueller

Lear method

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

real(kind=wp), public, dimension(:,:), allocatable :: cnm
real(kind=wp), public, dimension(:,:), allocatable :: snm

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure, public :: get_acc => compute_gravity_acceleration_lear

Pines method

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

real(kind=wp), public, dimension(:,:), allocatable :: cnm
real(kind=wp), public, dimension(:,:), allocatable :: snm

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure, public :: get_acc => compute_gravity_acceleration_pines

Pines (normalized) method

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

real(kind=wp), public, dimension(:,:), allocatable :: cnm
real(kind=wp), public, dimension(:,:), allocatable :: snm

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure, public :: get_acc => compute_gravity_acceleration_normalized_pines

Kuga/Carrara method

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

model name

character(len=:), public, allocatable :: filename

model file name

integer, public :: nmax = 0

degree of the model

integer, public :: mmax = 0

order of the model

real(kind=wp), public :: re = zero

body radius [km]

real(kind=wp), public :: mu = zero

body grav. parameter [km3/s2]

real(kind=wp), public, dimension(:,:), allocatable :: cnm
real(kind=wp), public, dimension(:,:), allocatable :: snm

Type-Bound Procedures

procedure, public :: initialize => read_geopotential_file
procedure, public :: destroy => destroy_geopotential_model
procedure, public :: get_acc => compute_gravity_acceleration_kuga_carrara

Functions

private pure function number_of_coefficients(n, m) result(np)

Author
Jacob Williams
Date
9/20/2014

Number of (c,s) coefficients for n x m geopotential model Starting with n=2,m=0.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: n

degree

integer, intent(in) :: m

order

Return Value integer

number of coefficients

private function FL(n)

Author
Jacob Williams
Date
9/20/2014

The FL factorial function from [1].

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: n

Return Value real(kind=wp)

private pure function pinesnorm(mu, req, r_f, cnm, snm, nmax, mmax) result(accel)

Normalized Pines geopotential code.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: mu

gravitational constant [km^3/s^2]

real(kind=wp), intent(in) :: req

body equatorial radius [km]

real(kind=wp), intent(in), dimension(3) :: r_f

body-fixed Cartesian position vector [km]

real(kind=wp), intent(in), dimension(:,0:) :: cnm

c coefficients (Normalized)

real(kind=wp), intent(in), dimension(:,0:) :: snm

s coefficients (Normalized)

integer, intent(in) :: nmax

desired degree

integer, intent(in) :: mmax

desired order

Return Value real(kind=wp), dimension(3)

body-fixed Cartesian acceleration vector [km/s^2]


Subroutines

private subroutine destroy_geopotential_model(me)

Destroy a gravity model.

Arguments

Type IntentOptional Attributes Name
class(geopotential_model), intent(inout) :: me

private subroutine compute_gravity_acceleration_mueller(me, r, n, m, a)

Wrapper for Mueller method.

Arguments

Type IntentOptional Attributes Name
class(geopotential_model_mueller), intent(inout) :: me
real(kind=wp), intent(in), dimension(3) :: r
integer, intent(in) :: n
integer, intent(in) :: m
real(kind=wp), intent(out), dimension(3) :: a

private subroutine compute_gravity_acceleration_pines(me, r, n, m, a)

Wrapper for Pines method.

Arguments

Type IntentOptional Attributes Name
class(geopotential_model_pines), intent(inout) :: me
real(kind=wp), intent(in), dimension(3) :: r
integer, intent(in) :: n
integer, intent(in) :: m
real(kind=wp), intent(out), dimension(3) :: a

private subroutine compute_gravity_acceleration_lear(me, r, n, m, a)

Wrapper for Lear method.

Arguments

Type IntentOptional Attributes Name
class(geopotential_model_lear), intent(inout) :: me
real(kind=wp), intent(in), dimension(3) :: r
integer, intent(in) :: n
integer, intent(in) :: m
real(kind=wp), intent(out), dimension(3) :: a

private subroutine compute_gravity_acceleration_kuga_carrara(me, r, n, m, a)

Wrapper for Kuga/Carrara method.

Read more…

Arguments

Type IntentOptional Attributes Name
class(geopotential_model_kuga_carrara), intent(inout) :: me
real(kind=wp), intent(in), dimension(3) :: r
integer, intent(in) :: n
integer, intent(in) :: m
real(kind=wp), intent(out), dimension(3) :: a

private subroutine compute_gravity_acceleration_normalized_pines(me, r, n, m, a)

Wrapper for normalized Pines method.

Arguments

Type IntentOptional Attributes Name
class(geopotential_model_normalized_pines), intent(inout) :: me
real(kind=wp), intent(in), dimension(3) :: r
integer, intent(in) :: n
integer, intent(in) :: m
real(kind=wp), intent(out), dimension(3) :: a

private subroutine read_geopotential_file(me, filename, nmax, mmax, status_ok)

Author
Jacob Williams
Date
9/20/2014

Read the gravity coefficient file. Example file: ftp://ftp.csr.utexas.edu/pub/grav/EGM96.GEO.Z

Arguments

Type IntentOptional Attributes Name
class(geopotential_model), intent(inout) :: me
character(len=*), intent(in) :: filename
integer, intent(in) :: nmax
integer, intent(in) :: mmax
logical, intent(out) :: status_ok

private subroutine get_format_statement(str, fmt)

Author
Jacob Williams
Date
1/24/2015

Returns the format statement from a line in a .GEO gravity coefficient file.

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: str
character(len=*), intent(out) :: fmt

private subroutine convert(nmodel, cnm, snm)

Author
Jacob Williams
Date
9/20/2014

Based on the CONVERT subroutine from [1]. Unnormalizes the C,S coefficients.

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nmodel
real(kind=wp), intent(inout), dimension(nmodel,0:nmodel) :: cnm
real(kind=wp), intent(inout), dimension(nmodel,0:nmodel) :: snm

private subroutine gravpot(r, nmax, re, mu, c, s, fg)

Author
Jacob Williams
Date
1/25/2014

Spencer's implementation of the Pines algorithms from [1]

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in), dimension(3) :: r

position vector

integer, intent(in) :: nmax

degree/order

real(kind=wp), intent(in) :: re

body radius

real(kind=wp), intent(in) :: mu

grav constant

real(kind=wp), intent(in), dimension(nmax,0:nmax) :: c

C coefficients

real(kind=wp), intent(in), dimension(nmax,0:nmax) :: s

S coefficients

real(kind=wp), intent(out), dimension(3) :: fg

grav acceleration

private subroutine geopot(x, y, z, nmax, mmax, re, ksq, c, s, fx, fy, fz)

Compute the gravitational acceleration vector using the Mueller method.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: x

position vector x-component

real(kind=wp), intent(in) :: y

position vector y-component

real(kind=wp), intent(in) :: z

position vector z-component

integer, intent(in) :: nmax

degree of model

integer, intent(in) :: mmax

order+1 of model

real(kind=wp), intent(in) :: re

body radius

real(kind=wp), intent(in) :: ksq

body GM

real(kind=wp), intent(in), dimension(:) :: c

C coefficients

real(kind=wp), intent(in), dimension(:) :: s

S coefficients

real(kind=wp), intent(out) :: fx

gravitational acceleration x-component

real(kind=wp), intent(out) :: fy

gravitational acceleration y-component

real(kind=wp), intent(out) :: fz

gravitational acceleration z-component

private subroutine grav(mu, rgr, rbar, nmodel, mmodel, cnm, snm, agr)

Author
Jacob Williams
Date
9/20/2014

Based on the GRAV subroutine from [1].

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: mu

gravitational constant

real(kind=wp), intent(in), dimension(3) :: rgr

position vector [body-fixed coordinates]

real(kind=wp), intent(in) :: rbar

gravitational scaling radius (generally the equatorial radius)

integer, intent(in) :: nmodel

the degree of the gravity model (>=2)

integer, intent(in) :: mmodel

the order of the gravity model (>=0, <=nmodel)

real(kind=wp), intent(in), dimension(nmodel,0:nmodel) :: cnm

C gravity coefficients

real(kind=wp), intent(in), dimension(nmodel,0:nmodel) :: snm

S gravity coefficients

real(kind=wp), intent(out), dimension(3) :: agr

gravitational acceleration vector [body-fixed coordinates]

private subroutine kuga_carrara_geopotential(nmax, nm, re, gm, c, s, x, ac)

Compute geopotential acceleration using the Kuga/Carrara algorithm. Based on Leg_ForCol_Ac from [1].

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nmax

max. order and degree loaded

integer, intent(in) :: nm

desired order and degree (nm <= nmax)

real(kind=wp), intent(in) :: re

body equatorial radius [km]

real(kind=wp), intent(in) :: gm

gravitational constant [km3/s2]

real(kind=wp), intent(in), dimension(nmax,0:nm) :: c

c coefficients (Normalized)

real(kind=wp), intent(in), dimension(nmax,0:nm) :: s

s coefficients (Normalized)

real(kind=wp), intent(in), dimension(3) :: x

body-fixed cartesian position vector [km]

real(kind=wp), intent(out), dimension(3) :: ac

body-fixed cartesian acceleration vector [km/s2]

public subroutine geopotential_module_test()

Author
Jacob Williams
Date
9/20/2014

Unit test routine for geopotential_module

Arguments

None