descriptors_m.f90 Source File


Source Code

module descriptors_m
    !! definition of descriptors, i.e. integer parameters
    use screen_io_m, only : get_stderr
    implicit none
    save

    public :: convert_descriptor_char_int

    integer, parameter ::BNDLOCATION_WALL   = 31
    !! point related with wall boundary condition
    integer, parameter ::BNDLOCATION_CORE   = 32
    !! point related with core boundary condition
    integer, parameter ::BNDLOCATION_OTHER  = 33
    !! point related with shadow boundary condition

    integer, parameter ::DISTRICT_CORE          = 813
    !! point located in core (outside actual computational domain, rho<rhomin)
    integer, parameter ::DISTRICT_CLOSED        = 814
    !! point located in closed field line region (within computational domain)
    integer, parameter ::DISTRICT_SOL           = 815
    !! point located in scrape-off layer (within computational domain)
    integer, parameter ::DISTRICT_PRIVFLUX      = 816
    !! point located in private flux region (within computational domain)
    integer, parameter ::DISTRICT_WALL          = 817
    !! point located in wall (outside computational domain, rho>rhomax)
    integer, parameter ::DISTRICT_DOME          = 818
    !! point located in divertor dome (outside computational domain, e.g. rho<rhomin_privflux)
    integer, parameter ::DISTRICT_OUT           = 819
    !! point located outside additional masks, i.e. shadow region (outside computational domain)

    integer, parameter ::BND_TYPE_DIRICHLET_ZERO    = -3
    !! Dirichlet boundary condition zeroth order
    integer, parameter ::BND_TYPE_DIRICHLET         = 0
    !! Dirichlet boundary condition first order (NOT WORKING YET, DO NOT USE)
    integer, parameter ::BND_TYPE_NEUMANN           = 1
    !! Neumann boundary condition first order
    integer, parameter ::BND_TYPE_NONE              = 312
    !! nothing applied for boundary conditions

    integer, parameter :: POINT_PGHOST_FIRST      = 253
    !! Point is ghost point, with connection (at least one next neighbor within grid) to grid
    integer, parameter :: POINT_PGHOST_DEEP       = 254
    !! Point is deeper ghost point, without connection to grid
    integer, parameter :: POINT_INNER_EDGE        = 255
    !! Point is grid point, with connection to pghost
    integer, parameter :: POINT_INNER_FULL        = 256
    !! Point is grid point, with connection fully within grid

    integer, parameter :: ERR_UNHANDLED               = 11
    integer, parameter :: ERR_PARAMETER_FILE          = 21

contains

    subroutine convert_descriptor_char_int(char_descr, int_descr)
        !! converts character, e.g. as specified in parameter files, into actual (integer) descriptor
        implicit none

        character(len=*), intent(in) :: char_descr
        !! character descriptor
        integer, intent(out) :: int_descr
        !! actual descriptor for code

        select case(char_descr)

            case ('BND_TYPE_DIRICHLET_ZERO')
                int_descr = BND_TYPE_DIRICHLET_ZERO
            case ('BND_TYPE_DIRICHLET')
                int_descr = BND_TYPE_DIRICHLET
            case ('BND_TYPE_NEUMANN')
                int_descr = BND_TYPE_NEUMANN
            case ('BND_TYPE_NONE')
                int_descr = BND_TYPE_NONE

            case default

                write(get_stderr(), *) &
                    'error(convert_descriptor_char_int): &
                    &char_descr not valid: ',char_descr
                ERROR STOP ERR_UNHANDLED

        end select

    end subroutine convert_descriptor_char_int

end module descriptors_m