polar_grid_m.f90 Source File


Source Code

module polar_grid_m
    !! Module implementing polar grid
    !! The polar grid has dimension (nrho, ntheta) with uniform grid spacing
    !! rho is the radial coordinate as prescribed by the equilibrium
    !! theta is the geometric poloidal angle
    use netcdf
    use precision_m, only : FP, FP_NAN, FP_EPS
    use constants_m, only : two_pi
    use comm_handling_m, only: is_master
    use equilibrium_m, only: equilibrium_t
    use circular_equilibrium_m, only : circular_t
    use slab_equilibrium_m, only : slab_t
    use coords_polar_m, only : polar_to_cart, jacobian_polar
    implicit none

    type, public :: polar_grid_t
        !! Polar grid
        real(FP), private :: phi
        !! Toroidal angle phi of polar grid
        real(FP), private :: rhopol_min
        !! Minimum rho of polar grid
        real(FP), private :: rhopol_max
        !! Maximum rho of polar grid
        integer, private :: nrho
        !! Number of radial grid points
        integer, private :: ntheta
        !! Number of poloidal grid points
        real(FP), private :: drho
        !! Radial grid distance
        real(FP), private :: dtheta
        !! Poloidal grid distance
    contains
        ! Getters for metainformation of mesh
        procedure, public :: initialize => initialize_polar_grid
        procedure, public :: get_phi
        procedure, public :: get_rhopol_min
        procedure, public :: get_rhopol_max
        procedure, public :: get_nrho
        procedure, public :: get_ntheta
        procedure, public :: get_drho
        procedure, public :: get_dtheta
        procedure, public :: get_rho
        procedure, public :: get_theta
        procedure, public :: fluxsurf_area
        procedure, public :: fluxsurf_vol
        procedure, public :: display => display_polar_grid
        final :: destructor

        procedure, public :: write_netcdf => write_netcdf_polar
        procedure, public :: read_netcdf => read_netcdf_polar
    end type

    interface

        module subroutine initialize_polar_grid(self, equi, phi, nrho, ntheta)
             !! Displays information for polar grid
            class(polar_grid_t), intent(inout) :: self
            !! Instance of the type
            class(equilibrium_t), intent(inout) :: equi
            !! Equilibrium
            real(FP), intent(in) :: phi
            !! Toroidal angle
            integer, intent(in) :: nrho
            !! Number of radial grid points
            integer, intent(in) :: ntheta
            !! Number of poloidal grid points
        end subroutine

        pure real(FP) module function get_phi(self)
            !! Returns toroidal angle phi
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end function

        pure real(FP) module function get_rhopol_min(self)
            !! Gets rhopol_min
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end function

        pure real(FP) module function get_rhopol_max(self)
            !! Gets rhopol_max
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end function

        pure integer module function get_nrho(self)
            !! Gets nrho
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end function

        pure integer module function get_ntheta(self)
            !! Gets ntheta
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end function

        pure real(FP) module function get_drho(self)
            !! Gets drho
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end function

        pure real(FP) module function get_dtheta(self)
            !! Gets dtheta
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end function

        pure real(FP) module function get_rho(self, ip)
            !! Computes rho at point ip
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
            integer, intent(in) :: ip
            !! Radial grid index
        end function

        pure real(FP) module function get_theta(self, jp)
            !! Computes rho at point ip
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
            integer, intent(in) :: jp
            !! Poloidal grid index
        end function

        real(FP) module function fluxsurf_area(self, equi, ip)
            !! Computes total area of flux surface
            !! Assumes axisymmetry
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
            class(equilibrium_t), intent(inout) :: equi
            !! Equilibrium
            integer, intent(in) :: ip
            !! Radial grid index
        end function

        real(FP) module function fluxsurf_vol(self, equi, ip)
            !! Computes the volume of flux surface
            !! Radial extent of [rho-drho/2, rho + drho/2]
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
            class(equilibrium_t), intent(inout) :: equi
            !! Equilibrium
            integer, intent(in) :: ip
            !! Radial grid index
        end function

        module subroutine write_netcdf_polar(self, equi, fgid)
            !! Writes information about the polar_grid_t
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
            class(equilibrium_t), intent(inout) :: equi
            !! Equilibrium
            integer, intent(in) :: fgid
            !! File or group id number of existing Netcdf4 file
        end subroutine

        module subroutine read_netcdf_polar(self, fgid)
            !! Reads information about the polar_grid_t
            class(polar_grid_t), intent(inout) :: self
            !! Instance of the type
            integer, intent(in) :: fgid
            !! File or group id number of existing Netcdf4 file
        end subroutine

        module subroutine display_polar_grid(self)
             !! Displays information for polar grid
            class(polar_grid_t), intent(in) :: self
            !! Instance of the type
        end subroutine

        module subroutine destructor(self)
            !! Frees memory associated with polar_grid_t
            type(polar_grid_t), intent(inout) :: self
            !! Instance of the type
        end subroutine

    end interface

end module