Skip to content

Commit

Permalink
Merge pull request #1404 from emkemp/fix/lisf75_imerg_alert
Browse files Browse the repository at this point in the history
Added alerts for missing/bad IMERG files.
  • Loading branch information
jvgeiger authored Aug 29, 2023
2 parents 26f432e + 2a584dd commit 2f334cf
Show file tree
Hide file tree
Showing 25 changed files with 481 additions and 98 deletions.
4 changes: 2 additions & 2 deletions lis/core/LIS_fileIOMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2966,7 +2966,7 @@ subroutine putget_int ( buffer, iofunc, file_name, &
!EOP

character*9 :: cstat
character*100 :: message (20)
character*255 :: message (20)
integer :: rec_length
integer :: istat
integer :: istat1
Expand Down Expand Up @@ -3108,7 +3108,7 @@ subroutine putget_real ( buffer, iofunc, file_name, &
! \end{description}
!EOP

character*100 :: message (20)
character*255 :: message (20)
integer :: rec_length
character*9 :: cstat
integer :: istat
Expand Down
4 changes: 2 additions & 2 deletions lis/core/LIS_historyMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7291,7 +7291,7 @@ subroutine writevar_grib1_withstats_real(ftn, ftn_stats, n, &
! call to compute diagnostic statistics of a variable
! \end{description}
!EOP
character*100 :: message(20)
character*255 :: message(20)
integer :: igrib
character*8 :: date
integer :: idate,idate1
Expand Down Expand Up @@ -7646,7 +7646,7 @@ subroutine writevar_grib2_withstats_real(ftn, ftn_stats, n, &
! call to compute diagnostic statistics of a variable
! \end{description}
!EOP
character*100 :: message(20)
character*255 :: message(20)
integer :: igrib
character*8 :: date
integer :: idate,idate1
Expand Down
6 changes: 3 additions & 3 deletions lis/core/LIS_logMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@ subroutine LIS_abort( abort_message )

implicit none

character*100 :: abort_message(20)
character*255 :: abort_message(20)

! !DESCRIPTION:
!
Expand Down Expand Up @@ -270,7 +270,7 @@ subroutine LIS_alert( program_name, alert_number, message )
!EOP
character*3 :: calert_number
character*7 :: iofunc
character*37 :: message_file
character*255 :: message_file
integer :: i
integer :: istat
integer :: ftn
Expand All @@ -295,7 +295,7 @@ subroutine LIS_alert( program_name, alert_number, message )
iofunc = 'opening'
ftn = LIS_getNextUnitNumber()
open (unit = ftn, &
file = message_file, &
file = trim(message_file), &
iostat = istat)

! ------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion lis/core/LIS_timeMgrMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2739,7 +2739,7 @@ subroutine LIS_julhr_date( julhr, yyyy,mm,dd,hh)
! \end{description}
!
!EOP
character*100 :: message ( 20 )
character*255 :: message ( 20 )

! ------------------------------------------------------------------
! executable code begins here... use LIS_tmjul4 to convert julhr to
Expand Down
4 changes: 2 additions & 2 deletions lis/metforcing/galwem/read_galwem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ subroutine read_galwem(n, findex, order, gribfile, rc)
character*100 :: gtype
integer :: file_julhr
integer :: yr1, mo1, da1, hr1
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: iginfo ( 40 )
real :: gridres_dlat, gridres_dlon
integer :: ifguess, jfguess
Expand Down Expand Up @@ -227,7 +227,7 @@ subroutine fldbld_read_galwem(n, findex, order, gribfile, ifguess, jfguess,&
!
!EOP
character*9 :: cstat
character*100 :: message ( 20 )
character*255 :: message ( 20 )
character(len=7) :: grib_msg
character(len=7) :: check_galwem_message
integer :: count_tair, count_qair
Expand Down
4 changes: 2 additions & 2 deletions lis/metforcing/galwem_ge/read_galwemge.F90
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ subroutine read_galwemge(n, m, findex, order, gribfile, rc)
character*100 :: gtype
integer :: file_julhr
integer :: yr1, mo1, da1, hr1
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: iginfo ( 40 )
real :: gridres_dlat, gridres_dlon
integer :: ifguess, jfguess
Expand Down Expand Up @@ -282,7 +282,7 @@ subroutine fldbld_read_galwemge(n, findex, order, gribfile, ifguess, jfguess,
!
!EOP
character*9 :: cstat
character*100 :: message ( 20 )
character*255 :: message ( 20 )
character(len=7) :: grib_msg
character(len=7) :: check_galwemge_message
integer :: count_tair, count_qair
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_cdfs2_est.F90
Original file line number Diff line number Diff line change
Expand Up @@ -204,7 +204,7 @@ subroutine AGRMET_cdfs2_est( n,k, cliprc, clippd,&
!EOP
character*10 :: date10
character*120 :: ifil
character*100 :: message(20)
character*255 :: message(20)
integer, allocatable :: times ( :, : , : )
integer*1, allocatable :: totalc ( :, : , : )
real :: cldtim(LIS_rc%lnc(n), LIS_rc%lnr(n))
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_fillgaps.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ subroutine AGRMET_fillgaps(n,ip,varfield)
logical :: foundPt
integer :: i,j,str,enr,stc,enc,kk
integer :: try
character*100 :: message (20)
character*255 :: message (20)


try = 0
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_fldbld.F90
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ subroutine AGRMET_fldbld(n,order,julhr)
!EOP

integer :: rc
character(len=100) :: message(20)
character(len=255) :: message(20)
character(len=10) :: yyyymmddhh
integer :: ierr

Expand Down
4 changes: 2 additions & 2 deletions lis/metforcing/usaf/AGRMET_fldbld_galwem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ subroutine AGRMET_fldbld_galwem(n,order,julhr,rc)
integer :: ftn, igrib
character*120 :: gribfile
integer :: yr1, mo1, da1, hr1
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: iginfo ( 40 )
real :: gridres_dlat, gridres_dlon
integer :: ifguess, jfguess
Expand Down Expand Up @@ -448,7 +448,7 @@ subroutine AGRMET_fldbld_read_galwem(n, fg_filename, ifguess, jfguess, &
!
!EOP
character*9 :: cstat
character*100 :: message ( 20 )
character*255 :: message ( 20 )
character(len=4) :: grib_msg
character(len=4) :: AGRMET_check_galwem_message
integer :: count_hgt
Expand Down
6 changes: 3 additions & 3 deletions lis/metforcing/usaf/AGRMET_fldbld_gfs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -138,7 +138,7 @@ subroutine AGRMET_fldbld_gfs(n,order,julhr,rc)

integer :: nunit
integer :: ksec2 ( 10 )
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: iginfo ( 40 )
real :: ginfo ( 40 )
real :: gridres
Expand Down Expand Up @@ -741,7 +741,7 @@ subroutine AGRMET_fldbld_read_gfs( fg_filename, ifguess, jfguess,&
! \end{description}
!EOP
character*9 :: cstat
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: count_dpd
integer :: count_hgt
integer :: count_rh
Expand Down Expand Up @@ -1796,7 +1796,7 @@ integer function set_plevel(editionNumber,pds9,level)
! Locals
integer :: plevel
integer :: ierr
character(len=100) :: messages(20)
character(len=255) :: messages(20)

if (editionNumber == 1) then
plevel = pds9
Expand Down
4 changes: 2 additions & 2 deletions lis/metforcing/usaf/AGRMET_fldbld_precip_galwem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,7 @@ subroutine AGRMET_fldbld_precip_galwem(n,julhr,fc_hr,fg_data)
character*120 :: avnfile, avnfile2
integer :: yr1, mo1, da1, hr1
integer :: julhr
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: iginfo ( 2 )
real :: gridres
integer :: alert_number
Expand Down Expand Up @@ -508,7 +508,7 @@ subroutine AGRMET_fldbld_read_precip_galwem(fg_filename, ifguess, jfguess,&
!
!EOP
character*9 :: cstat
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: count_prec
integer :: i
integer :: ierr
Expand Down
4 changes: 2 additions & 2 deletions lis/metforcing/usaf/AGRMET_fldbld_precip_gfs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,7 @@ subroutine AGRMET_fldbld_precip_gfs(n,findex,julhr,fc_hr,gfsdata)
integer :: julhr
integer :: nunit, nunit2
integer :: ksec2 ( 10 )
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: iginfo ( 40 )
real :: ginfo ( 40 )
real :: gridres
Expand Down Expand Up @@ -587,7 +587,7 @@ subroutine AGRMET_fldbld_read_precip_gfs( fg_filename, ifguess, jfguess,&
!
!EOP
character*9 :: cstat
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: count_prec
integer :: file_age
integer :: i
Expand Down
3 changes: 2 additions & 1 deletion lis/metforcing/usaf/AGRMET_forcingMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -820,7 +820,8 @@ subroutine init_AGRMET(findex)
integer :: kprs
byte, allocatable :: buffer(:,:,:)
character*9 :: cstat
character*100 :: file_name,file_nam,message (20)
character*100 :: file_name,file_nam
character*255 :: message(20)
integer :: rec_length
integer :: istat
integer :: istat1
Expand Down
61 changes: 53 additions & 8 deletions lis/metforcing/usaf/AGRMET_getpcpobs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -32,13 +32,15 @@
! 7 Feb 11 Enable use of either JMOBS or CDMS obs......Chris Franks/16WS/WXE/SEMS
! 11 May 11 Store obs from 3,9,15,& 21Z for India and Sri Lanka in a
! new array and pass to processobs............Chris Franks/16WS/WXE/SEMS
! !INTERFACE:
! 29 Aug 23 Call LIS_alert if a preobs file is missing..............Eric Kemp/NASA
!
! !INTERFACE:
subroutine AGRMET_getpcpobs(n, j6hr, month, prcpwe, &
use_twelve, p6, p12, alert_number, precip6, precip12,pcp_src)
! !USES:
use LIS_coreMod, only : LIS_rc
use LIS_coreMod, only : LIS_rc, LIS_masterproc
use LIS_timeMgrMod, only : LIS_tick, LIS_julhr_date
use LIS_logMod, only : LIS_logunit
use LIS_logMod, only : LIS_logunit, LIS_alert
use AGRMET_forcingMod, only : agrmet_struc
use USAF_bratsethMod, only: USAF_ObsData, USAF_setbratsethprecipstats

Expand Down Expand Up @@ -173,10 +175,9 @@ subroutine AGRMET_getpcpobs(n, j6hr, month, prcpwe, &
integer :: nsize3
integer :: yr,mo,da,hr
integer :: ierr1, ierr2, ierr3
integer :: k
integer :: k
logical :: cdms_flag


character(255) :: message(20)

type rain_obs
sequence
Expand Down Expand Up @@ -279,9 +280,31 @@ subroutine AGRMET_getpcpobs(n, j6hr, month, prcpwe, &
write(LIS_logunit,*)"* OBSERVATIONS BEYOND ARRAY SIZE WILL BE IGNORED."
write(LIS_logunit,*)"******************************************************"
write(LIS_logunit,*)' '


!EMK 20230829...Create alert file.
message(:) = ''
message(1) = '[WARN] Program: LIS'
message(2) = ' Routine: AGRMET_getpcpobs'
message(3) = ' Too many rain gage reports in '// &
trim(filename)
! message(4) = ' Number of rain gage reports is '// nsize
write(message(5),'(A, I6)') &
' Number of rain gage reports is ', nsize
!message(5) = ' Array size is '// &
! agrmet_struc(n)%max_pcpobs
write(message(5),'(A, I6)') ' Array size is ', &
agrmet_struc(n)%max_pcpobs
message(6) = ' Observations beyond array size will be ignored'
message(7) = ' Increase number of AGRMET maximum precip obs in lis.config file!'
if (LIS_masterproc) then
call LIS_alert('LIS.AGRMET_getpcpobs', &
alert_number, message)
alert_number = alert_number + 1
end if

nsize = agrmet_struc(n)%max_pcpobs


end if

cdms_count = 0
Expand Down Expand Up @@ -367,7 +390,17 @@ subroutine AGRMET_getpcpobs(n, j6hr, month, prcpwe, &
write(LIS_logunit,*)'*** ERROR ON DATABASE READ. ISTAT IS '
write(LIS_logunit,*)'**********************************************'
write(LIS_logunit,*)' '


!EMK 20230829...Create alert file.
message(:) = ''
message(1) = '[WARN] Program: LIS'
message(2) = ' Routine: AGRMET_getpcpobs'
message(3) = ' Problem reading '// trim(filename)
if (LIS_masterproc) then
call LIS_alert('LIS.AGRMET_getpcpobs', &
alert_number, message)
alert_number = alert_number + 1
end if
end if
else
write(LIS_logunit,*)' '
Expand All @@ -376,6 +409,18 @@ subroutine AGRMET_getpcpobs(n, j6hr, month, prcpwe, &
write(LIS_logunit,*) trim(filename)
write(LIS_logunit,*)'**********************************************'
write(LIS_logunit,*)' '

!EMK 20230829...Create alert file.
message(:) = ''
message(1) = '[WARN] Program: LIS'
message(2) = ' Routine: AGRMET_getpcpobs'
message(3) = ' Missing rain gage file '// trim(filename)
if (LIS_masterproc) then
call LIS_alert('LIS.AGRMET_getpcpobs', &
alert_number, message)
alert_number = alert_number + 1
end if

endif

!-----------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_julhr_date10.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ subroutine AGRMET_julhr_date10( julhr, date10)
! convert julian hour to hour,day,month and year
! \end{description}
!EOP
character*100 :: message ( 20 )
character*255 :: message ( 20 )
integer :: dd
integer :: hh
integer :: j
Expand Down
3 changes: 2 additions & 1 deletion lis/metforcing/usaf/AGRMET_makest.F90
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,8 @@ subroutine AGRMET_makest(n,findex,j6hr,estpcp,source,cdfs2est,prcpwe, use_twelve
logical, intent(out) :: cmorphpixel(LIS_rc%lnc(n), LIS_rc%lnr(n),4)
! declarations for readmask in geoprecip latlon
character*9 :: cstat
character*100 :: file_name,file_nam,message (20)
character*100 :: file_name,file_nam
character*255 :: message(20)
integer :: rec_length
integer :: istat
integer :: istat1
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_read_sfcalccntm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ subroutine AGRMET_read_sfcalccntm(n)
!EOP

logical :: exists
character*100 :: message(20)
character*255 :: message(20)
integer :: ftn
real :: data_in(LIS_rc%gnc(n), LIS_rc%gnr(n))
integer :: istat
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_readmask.F90
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ subroutine AGRMET_readmask(n)
integer :: hemi, start, end
logical :: exists
character*100 :: name
character*100 :: message(20)
character*255 :: message(20)
character*30 :: routine_name

data routine_name / 'AGRMET_readmask' /
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_readpcpcntm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ subroutine AGRMET_readpcpcntm(n)

logical :: exists
character*100 :: name
character*100 :: message(20)
character*255 :: message(20)
integer :: ftn
real :: data_in(LIS_rc%gnc(n), LIS_rc%gnr(n))
integer :: istat
Expand Down
2 changes: 1 addition & 1 deletion lis/metforcing/usaf/AGRMET_readterrain.F90
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ subroutine AGRMET_readterrain(n)
integer :: hemi
logical :: exists
character*100 :: name
character*100 :: message(20)
character*255 :: message(20)
character*30 :: routine_name

data routine_name / 'AGRMET_readterrain' /
Expand Down
Loading

0 comments on commit 2f334cf

Please sign in to comment.