Skip to content

Commit

Permalink
Add <error> argument to rads_set_phase
Browse files Browse the repository at this point in the history
  • Loading branch information
remkos committed May 30, 2018
1 parent c8ce21c commit ea274ec
Showing 1 changed file with 38 additions and 12 deletions.
50 changes: 38 additions & 12 deletions src/rads.f90
Original file line number Diff line number Diff line change
Expand Up @@ -492,11 +492,12 @@ module rads
! Set the pointer to satellite phase info within the S struct
!
! SYNTAX
! subroutine rads_set_phase (S, name <or> cycle <or> time)
! subroutine rads_set_phase (S, name <or> cycle <or> time, error)
! type(rads_sat), intent(inout) :: S
! character(len=*), intent(in) :: name <or>
! integer(fourbyteint), intent(in) :: cycle <or>
! real(eightbytereal), intent(in) :: time
! logical, optional, intent(out) :: error
!
! PURPOSE
! Set the pointer S%phase to the proper phase definitions for the mission
Expand All @@ -509,6 +510,12 @@ module rads
!
! For efficiency, the routine first checks if the current phase is correct.
!
! If no matching phase can be found the outcome depends on the use of the
! optional argument <error>:
! - If <error> is present, then <error> will refurn .true. (otherwise .false.)
! - If <error> is not present, the routine prints an error message and the
! calling program stops.
!
! ARGUMENTS
! S : Satellite/mission dependent structure
! name : Name of phase
Expand Down Expand Up @@ -1305,6 +1312,7 @@ subroutine rads_open_pass (S, P, cycle, pass, rw)
character(len=rads_strl) :: string
integer(fourbyteint) :: i, j1, j2, k, ascdes, ncid
real(eightbytereal), pointer :: temp(:,:)
logical :: error

! Initialise
S%error = rads_warn_nc_file
Expand All @@ -1315,8 +1323,11 @@ subroutine rads_open_pass (S, P, cycle, pass, rw)

if (rads_verbose >= 2) write (*,'(a,a3,2i5)') 'Checking sat/cycle/pass : ', S%sat, cycle, pass

! If the cycle is out of range for the current phase, look for a new phase
call rads_set_phase (S, cycle, error)

! Do checking on cycle limits
if (cycle < S%cycles(1) .or. cycle > S%cycles(2)) then
if (error) then
S%pass_stat(1) = S%pass_stat(1) + 1
return
endif
Expand All @@ -1329,9 +1340,6 @@ subroutine rads_open_pass (S, P, cycle, pass, rw)
endif
endif

! If the cycle is out of range for the current phase, look for a new phase
call rads_set_phase (S, cycle)

! Do checking on pass limits (which may include new phase limits)
if (pass < S%passes(1) .or. pass > S%passes(2) .or. pass > S%phase%passes) then
S%pass_stat(2) = S%pass_stat(2) + 1
Expand Down Expand Up @@ -3678,10 +3686,12 @@ function rads_get_phase (S, name, allow_new) result (phase)
phase => S%phases(n)
end function rads_get_phase

subroutine rads_set_phase_by_name (S, name)
subroutine rads_set_phase_by_name (S, name, error)
type(rads_sat), intent(inout) :: S
character(len=*), intent(in) :: name
logical, optional, intent(out) :: error
integer :: i
if (present(error)) error = .false.
! Check if we are already in the right mission phase
if (name(1:1) == S%phase%name(1:1)) return
! Check all mission phases
Expand All @@ -3691,14 +3701,20 @@ subroutine rads_set_phase_by_name (S, name)
return
endif
enddo
call rads_exit ('No such mission phase "'//name//'" for satellite "'//S%sat//'"')
if (present(error)) then
error = .true.
else
call rads_exit ('No such mission phase "'//name//'" for satellite "'//S%sat//'"')
endif
end subroutine rads_set_phase_by_name

subroutine rads_set_phase_by_cycle (S, cycle)
subroutine rads_set_phase_by_cycle (S, cycle, error)
type(rads_sat), intent(inout) :: S
integer(fourbyteint), intent(in) :: cycle
logical, optional, intent(out) :: error
integer :: i
character(len=3) :: name
if (present(error)) error = .false.
! Check if we are already in the right mission phase
if (cycle >= S%phase%cycles(1) .and. cycle <= S%phase%cycles(2)) return
! Check all mission phases
Expand All @@ -3708,15 +3724,21 @@ subroutine rads_set_phase_by_cycle (S, cycle)
return
endif
enddo
write (name, '(i3.3)') cycle
call rads_exit ('No cycle '//name//' for any mission phase of satellite "'//S%sat//'"')
if (present(error)) then
error = .true.
else
write (name, '(i3.3)') cycle
call rads_exit ('No cycle '//name//' for any mission phase of satellite "'//S%sat//'"')
endif
end subroutine rads_set_phase_by_cycle

subroutine rads_set_phase_by_time (S, time)
subroutine rads_set_phase_by_time (S, time, error)
use rads_time
type(rads_sat), intent(inout) :: S
real(eightbytereal), intent(in) :: time
logical, optional, intent(out) :: error
integer :: i
if (present(error)) error = .false.
! Check if we are already in the right mission phase
if (time >= S%phase%start_time .and. time <= S%phase%end_time) return
! Check all mission phases
Expand All @@ -3726,7 +3748,11 @@ subroutine rads_set_phase_by_time (S, time)
return
endif
enddo
call rads_exit ('Time '//strf1985f(time)//' is outside any mission phase of satellite "'//S%sat//'"')
if (present(error)) then
error = .true.
else
call rads_exit ('Time '//strf1985f(time)//' is outside any mission phase of satellite "'//S%sat//'"')
endif
end subroutine rads_set_phase_by_time

!****f* rads/rads_predict_equator
Expand Down

0 comments on commit ea274ec

Please sign in to comment.