Skip to content

Commit

Permalink
added ability to specify file dirs.
Browse files Browse the repository at this point in the history
moved files into data directories
  • Loading branch information
jacobwilliams committed Feb 10, 2024
1 parent 62c345d commit 5c4b824
Show file tree
Hide file tree
Showing 24 changed files with 79 additions and 6 deletions.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
19 changes: 19 additions & 0 deletions src/core.f90
Original file line number Diff line number Diff line change
Expand Up @@ -22,12 +22,31 @@ module core
contains
private
procedure,public :: get_flux => get_flux_
procedure,public :: set_data_files_paths
end type radbelt_type

public :: get_flux !! simple function version for testing

contains

!*****************************************************************************************
!>
! Set the paths to the data files.
! If not used or blank, the folder `data/aep8` and `data/igrf` in the
! current working directory is assumed

subroutine set_data_files_paths(me, aep8_dir, igrf_dir)

class(radbelt_type),intent(inout) :: me
character(len=*),intent(in) :: aep8_dir
character(len=*),intent(in) :: igrf_dir

call me%trm%set_data_file_dir(trim(aep8_dir))
call me%igrf%set_data_file_dir(trim(igrf_dir))

end subroutine set_data_files_paths
!*****************************************************************************************

!*****************************************************************************************
!>
! Calculate the flux of trapped particles at a specific location and time.
Expand Down
35 changes: 31 additions & 4 deletions src/shellig.f90
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,8 @@ module shellig_module
type,public :: shellig_type
private

character(len=:),allocatable :: igrf_dir !! directory containing the data files

! formerly in the `fidb0` common block
real(wp),dimension(3) :: sp = 0.0_wp

Expand All @@ -49,7 +51,7 @@ module shellig_module

! formerly in `model` common block
integer :: iyea = 0 !! the int year corresponding to the file `name` that has been read
character(len=filename_len) :: name = '' !! file name
character(len=:),allocatable :: name !! file name
integer :: nmax = 0 !! maximum order of spherical harmonics
real(wp) :: Time = 0.0_wp !! year (decimal: 1973.5) for which magnetic field is to be calculated
real(wp),dimension(144) :: g = 0.0_wp !! `g(m)` -- normalized field coefficients (see [[feldcof]]) m=nmax*(nmax+2)
Expand All @@ -74,12 +76,37 @@ module shellig_module
procedure, public :: shellg
procedure, public :: findb0
procedure :: stoer, getshc, intershc, extrashc
procedure,public :: set_data_file_dir, get_data_file_dir

end type shellig_type

contains
!*****************************************************************************************

!*****************************************************************************************
!>
! Set the directory containing the data files.

subroutine set_data_file_dir(me,dir)
class(shellig_type),intent(inout) :: me
character(len=*),intent(in) :: dir
me%igrf_dir = trim(dir)
end subroutine set_data_file_dir

!*****************************************************************************************
!>
! Get the directory containing the data files.

function get_data_file_dir(me) result(dir)
class(shellig_type),intent(in) :: me
character(len=:),allocatable :: dir
if (allocated(me%igrf_dir)) then
dir = trim(me%igrf_dir) // '/'
else
dir = 'data/igrf/' ! default
end if
end function get_data_file_dir

!*****************************************************************************************
!>
! Wrapper for IGRF functions.
Expand Down Expand Up @@ -662,7 +689,7 @@ subroutine feldcof(me,year,dimo)

real(wp) :: dte1 , dte2 , erad , gha(144) , sqrt2
integer :: i , ier , j , l , m , n , iyea
character(len=filename_len) :: fil2
character(len=:),allocatable :: fil2
real(wp) :: x , f0 , f !! these were double precision in original
!! code while everything else was single precision

Expand Down Expand Up @@ -694,9 +721,9 @@ subroutine feldcof(me,year,dimo)
if ( l<1 ) l = 1
if ( l>numye ) l = numye
dte1 = dtemod(l)
me%name = filmod(l)
me%name = me%get_data_file_dir() // trim(filmod(l))
dte2 = dtemod(l+1)
fil2 = filmod(l+1)
fil2 = me%get_data_file_dir() // trim(filmod(l+1))
if (read_file) then
! get igrf coefficients for the boundary years
! [if they have not ready been loaded]
Expand Down
31 changes: 29 additions & 2 deletions src/trmfun.f90
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,8 @@ module trmfun_module
!! main class for the `aep8` model
private

character(len=:),allocatable :: aep8_dir !! directory containing the data files

! data read from the files:
character(len=:),allocatable :: file_loaded !! the file that has been loaded
integer,dimension(8) :: ihead = 0
Expand All @@ -38,10 +40,35 @@ module trmfun_module
private
procedure,public :: aep8 !! main routine
procedure,public :: trara1, trara2 !! low-level routine
procedure,public :: set_data_file_dir, get_data_file_dir
end type trm_type

contains

!*****************************************************************************************
!>
! Set the directory containing the data files.

subroutine set_data_file_dir(me,dir)
class(trm_type),intent(inout) :: me
character(len=*),intent(in) :: dir
me%aep8_dir = trim(dir)
end subroutine set_data_file_dir

!*****************************************************************************************
!>
! Get the directory containing the data files.

function get_data_file_dir(me) result(dir)
class(trm_type),intent(in) :: me
character(len=:),allocatable :: dir
if (allocated(me%aep8_dir)) then
dir = trim(me%aep8_dir) // '/'
else
dir = 'data/aep8/' ! default
end if
end function get_data_file_dir

!*****************************************************************************************
!>
! Main wrapper for the radiation model.
Expand All @@ -59,10 +86,10 @@ subroutine aep8(me,e,l,bb0,imname,flux)

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

name = mname(Imname) ! the file to load
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
Expand Down

0 comments on commit 5c4b824

Please sign in to comment.