aep8 Subroutine

private subroutine aep8(me, e, l, bb0, imname, flux)

Main wrapper for the radiation model. Reads the coefficient file and calls the low-level routine.

Type Bound

trm_type

Arguments

Type IntentOptional Attributes Name
class(trm_type), intent(inout) :: me
real(kind=wp), intent(in) :: e
real(kind=wp), intent(in) :: l
real(kind=wp), intent(in) :: bb0
integer, intent(in) :: imname

which model to load (index in mname array)

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

Calls

proc~~aep8~~CallsGraph proc~aep8 trmfun_module::trm_type%aep8 proc~get_data_file_dir~2 trmfun_module::trm_type%get_data_file_dir proc~aep8->proc~get_data_file_dir~2 proc~trara1 trmfun_module::trm_type%trara1 proc~aep8->proc~trara1 proc~trara2 trmfun_module::trm_type%trara2 proc~trara1->proc~trara2

Called by

proc~~aep8~~CalledByGraph proc~aep8 trmfun_module::trm_type%aep8 proc~get_flux_c_ radbelt_module::radbelt_type%get_flux_c_ proc~get_flux_c_->proc~aep8 proc~get_flux_g_ radbelt_module::radbelt_type%get_flux_g_ proc~get_flux_g_->proc~aep8 none~get_flux radbelt_module::radbelt_type%get_flux none~get_flux->proc~get_flux_c_ none~get_flux->proc~get_flux_g_ proc~get_flux_c radbelt_module::get_flux_c proc~get_flux_c->none~get_flux proc~get_flux_g radbelt_module::get_flux_g proc~get_flux_g->none~get_flux proc~get_flux_g_c radbelt_c_module::get_flux_g_c proc~get_flux_g_c->none~get_flux interface~get_flux radbelt_module::get_flux interface~get_flux->proc~get_flux_c interface~get_flux->proc~get_flux_g

Source Code

    subroutine aep8(me, e, l, bb0, imname, flux)

        class(trm_type), intent(inout) :: me

        real(wp), intent(in) :: e
        real(wp), intent(in) :: l
        real(wp), intent(in) :: bb0
        integer, intent(in) :: imname !! which model to load (index in `mname` array)
        real(wp), intent(out) :: flux

        real(wp) :: ee(1), f(1) !! temp variables
        integer :: i, ierr, iuaeap, nmap
        character(len=:), allocatable :: name
        logical :: load_file

        name = me%get_data_file_dir()//trim(mname(Imname)) ! the file to load

        ! JW : do we need to reset some or all of these ?
        me%fistep = 0.0_wp
        me%f1 = 1.001_wp
        me%f2 = 1.002_wp

        ! check to see if this file has already been loaded
        ! [the class can store one file at a time]
        load_file = .true.
        if (allocated(me%file_loaded)) then
            if (name == me%file_loaded) load_file = .false.
        end if

        if (load_file) then
            open (newunit=iuaeap, file=name, status='OLD', iostat=ierr, form='FORMATTED')
            if (ierr /= 0) then
                error stop 'error reading '//trim(name)
            end if
            read (iuaeap, '(1X,12I6)') me%ihead
            nmap = me%ihead(8)
            allocate (me%map(nmap))
            read (iuaeap, '(1X,12I6)') (me%map(i), i=1, nmap)
            close (iuaeap)
            me%file_loaded = trim(name)
        end if

        ee(1) = e
        call me%trara1(me%ihead, me%map, L, Bb0, ee, f, 1)
        flux = f(1)
        if (Flux > 0.0_wp) Flux = 10.0_wp**Flux

    end subroutine aep8