ROMS
Loading...
Searching...
No Matches
check_multifile.F File Reference
#include "cppdefs.h"
Include dependency graph for check_multifile.F:

Go to the source code of this file.

Functions/Subroutines

subroutine check_multifile (ng, model)
 
subroutine multifile_info_s1d (ng, model, file_type, s)
 
subroutine multifile_info_s2d (ng, model, file_type, inpfiles, idim, s)
 
logical function check_file (ng, model, nfiles, ncname, iotype, tmin, tmax, tscale, lcheck)
 

Function/Subroutine Documentation

◆ check_file()

logical function check_file ( integer, intent(in) ng,
integer, intent(in) model,
integer, intent(in) nfiles,
character (*), intent(in) ncname,
integer, intent(in) iotype,
real(dp), intent(out) tmin,
real(dp), intent(out) tmax,
real(dp), intent(out) tscale,
logical, intent(out) lcheck )

Definition at line 529 of file check_multifile.F.

531!
532!=======================================================================
533! !
534! This logical function scans the variables of the provided input !
535! NetCDF for the time record variable and gets its range of values. !
536! It used elsewhere to determine which input NetCDF multi-file is !
537! needed for initialization or restart. !
538! !
539! On Input: !
540! !
541! ng Nested grid number. !
542! model Calling model identifier. !
543! Nfiles Number of multi-files. !
544! ncname NetCDF file name to process (string). !
545! IOtype I/O processing library (integer): !
546! io_nf90 Standard NetCDF libray !
547! io_pio Parallel I/O library !
548! !
549! On Output: !
550! !
551! Tmin Available minimum time variable value. !
552! Tmax Available maximum time variable value. !
553! Tscale Scale to convert time variable units to seconds !
554! Lcheck Switch to indicate that the time range needs to be !
555! checked by the calling routine. !
556! foundit The value of the result is TRUE/FALSE if the !
557! time variable is found or not. !
558! !
559!=======================================================================
560!
561 USE mod_param
562 USE mod_parallel
563 USE mod_iounits
564 USE mod_ncparam
565 USE mod_netcdf
566#if defined PIO_LIB && defined DISTRIBUTE
568#endif
569 USE mod_scalars
570!
571 USE strings_mod, ONLY : founderror, lowercase
572!
573 implicit none
574!
575! Imported variable declarations.
576!
577 logical, intent(out) :: Lcheck
578!
579 integer, intent(in) :: ng, model, Nfiles, IOtype
580!
581 character (*), intent(in) :: ncname
582!
583 real(dp), intent(out) :: Tmin, Tmax, Tscale
584!
585! Local variable declarations.
586!
587 logical :: Lcycle, Lperpetual, Lspectral, foundit
588!
589 integer :: Nrec, TvarID, i, ncid, nvdim, nvatt
590!
591 character (len=40) :: Tunits, TvarName
592
593 character (len=*), parameter :: MyFile = &
594 & __FILE__//", check_file"
595
596#if defined PIO_LIB && defined DISTRIBUTE
597!
598 TYPE (File_desc_t) :: pioFile
599 TYPE (Var_desc_t) :: TvarDesc
600#endif
601!
602 sourcefile=myfile
603!
604!------------------------------------------------------------------------
605! Check if requested time is within the NetCDF file dataset.
606!------------------------------------------------------------------------
607!
608! Initialize.
609!
610 foundit=.false.
611 lcheck=.true.
612 lcycle=.false.
613 lperpetual=.false.
614 lspectral =.false.
615 tscale=1.0_r8 ! seconds
616 tmin=0.0_r8
617 tmax=0.0_r8
618!
619! Open NetCDF file for reading.
620!
621 SELECT CASE (iotype)
622 CASE (io_nf90)
623 CALL netcdf_open (ng, model, ncname, 0, ncid)
624#if defined PIO_LIB && defined DISTRIBUTE
625 CASE (io_pio)
626 CALL pio_netcdf_open (ng, model, ncname, 0, piofile)
627#endif
628 END SELECT
629 IF (founderror(exit_flag, noerror, __line__, myfile)) THEN
630 IF (master) WRITE (stdout,10) trim(ncname)
631 RETURN
632 END IF
633!
634! Inquire about all the variables
635!
636 SELECT CASE (iotype)
637 CASE (io_nf90)
638 CALL netcdf_inq_var (ng, model, ncname, &
639 & ncid = ncid)
640#if defined PIO_LIB && defined DISTRIBUTE
641 CASE (io_pio)
642 CALL pio_netcdf_inq_var (ng, model, ncname, &
643 & piofile = piofile)
644#endif
645 END SELECT
646 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
647!
648! Search for the time variable: any 1D array variable with the string
649! 'time' in the variable name.
650!
651 DO i=1,n_var
652 IF ((index(trim(lowercase(var_name(i))),'time').ne.0).and. &
653 & (var_ndim(i).eq.1)) THEN
654 tvarname=trim(var_name(i))
655 foundit=.true.
656 EXIT
657 ELSE IF ((index(trim(var_name(i)),'tide_period').ne.0).and. &
658 & (var_ndim(i).eq.1)) THEN
659 tvarname=trim(var_name(i))
660 foundit=.true.
661 lspectral=.true. ! we do not need to check tidal data
662 EXIT
663 END IF
664 END DO
665 IF (.not.foundit) THEN
666 IF (master) THEN
667 WRITE (stdout,20) trim(ncname)
668 END IF
669 exit_flag=4
670 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
671 END IF
672!
673! Inquire about requested variable.
674!
675 SELECT CASE (iotype)
676 CASE (io_nf90)
677 CALL netcdf_inq_var (ng, model, ncname, &
678 & ncid = ncid, &
679 & myvarname = trim(tvarname), &
680 & varid = tvarid, &
681 & nvardim = nvdim, &
682 & nvaratt = nvatt)
683#if defined PIO_LIB && defined DISTRIBUTE
684 CASE (io_pio)
685 CALL pio_netcdf_inq_var (ng, model, ncname, &
686 & piofile = piofile, &
687 & myvarname = trim(tvarname), &
688 & piovar = tvardesc, &
689 & nvardim = nvdim, &
690 & nvaratt = nvatt)
691#endif
692 END SELECT
693 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
694!
695! Set number of records available and check the 'units' attribute.
696! Also, set output logical switch 'Lcheck' for the calling to check
697! the available data time range. For example, we need to check it
698! there is enough data to finish the simulation. Notice that for
699! data with 'cycle_length', Lcheck = FALSE. Also, Lcheck = FALSE
700! for perpetual time axis: the 'calendar' attribute is 'none' or
701! the number of records in the time dimension is one (Nrec=1).
702!
703 nrec=var_dsize(1) ! time is a 1D array
704 DO i=1,nvatt
705 IF (trim(var_aname(i)).eq.'units') THEN
706 tunits=trim(var_achar(i))
707 IF (index(trim(var_achar(i)),'day').ne.0) THEN
708 tscale=86400.0_r8
709 ELSE IF (index(trim(var_achar(i)),'hour').ne.0) THEN
710 tscale=3600.0_r8
711 ELSE IF (index(trim(var_achar(i)),'second').ne.0) THEN
712 tscale=1.0_r8
713 END IF
714 ELSE IF (trim(var_aname(i)).eq.'calendar') THEN
715 IF (((nrec.eq.1).and.(nfiles.eq.1)).or. &
716 & (index(trim(var_achar(i)),'none').ne.0)) THEN
717 lperpetual=.true.
718 END IF
719 ELSE IF (trim(var_aname(i)).eq.'cycle_length') THEN
720 lcycle=.true.
721 END IF
722 END DO
723!
724! Turn off the checking of time range if cycling, perpectual, or
725! spectral time axis.
726!
727 IF (lcycle.or.lperpetual.or.lspectral.or. &
728 & ((nrec.eq.1).and.(nfiles.eq.1))) THEN
729 lcheck=.false.
730 END IF
731!
732! Read in time variable minimum and maximun values (input time units).
733!
734 SELECT CASE (iotype)
735 CASE (io_nf90)
736 CALL netcdf_get_time (ng, model, ncname, tvarname, &
737 & rclock%DateNumber, tmin, &
738 & ncid = ncid, &
739 & start = (/1/), &
740 & total = (/1/))
741 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
742!
743 CALL netcdf_get_time (ng, model, ncname, tvarname, &
744 & rclock%DateNumber, tmax, &
745 & ncid = ncid, &
746 & start = (/nrec/), &
747 & total = (/1/))
748 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
749
750#if defined PIO_LIB && defined DISTRIBUTE
751 CASE (io_pio)
752 CALL pio_netcdf_get_time (ng, model, ncname, tvarname, &
753 & rclock%DateNumber, tmin, &
754 & piofile = piofile, &
755 & start = (/1/), &
756 & total = (/1/))
757 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
758!
759 CALL pio_netcdf_get_time (ng, model, ncname, tvarname, &
760 & rclock%DateNumber, tmax, &
761 & piofile = piofile, &
762 & start = (/nrec/), &
763 & total = (/1/))
764 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
765#endif
766 END SELECT
767
768!
769! Close NetCDF file.
770!
771 SELECT CASE (iotype)
772 CASE (io_nf90)
773 CALL netcdf_close (ng, model, ncid, ncname, .false.)
774#if defined PIO_LIB && defined DISTRIBUTE
775 CASE (io_pio)
776 CALL pio_netcdf_close (ng, model, piofile, ncname, .false.)
777#endif
778 END SELECT
779 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
780!
781 10 FORMAT (/, ' CHECK_FILE - unable to open grid NetCDF file: ',a)
782 20 FORMAT (/, ' CHECK_FILE - unable to find time variable in input', &
783 & ' NetCDF file:', /, 14x, a, /, 14x, &
784 & 'variable name does not contains the "time" string.')
785!
786 RETURN
integer stdout
character(len=256) sourcefile
integer, parameter io_nf90
Definition mod_ncparam.F:95
integer, parameter io_pio
Definition mod_ncparam.F:96
subroutine, public netcdf_close(ng, model, ncid, ncname, lupdate)
character(len=1024), dimension(nvara) var_achar
Definition mod_netcdf.F:183
subroutine, public netcdf_open(ng, model, ncname, omode, ncid)
integer, dimension(mvars) var_ndim
Definition mod_netcdf.F:164
character(len=100), dimension(mvars) var_name
Definition mod_netcdf.F:169
integer n_var
Definition mod_netcdf.F:152
integer, dimension(nvard) var_dsize
Definition mod_netcdf.F:177
character(len=100), dimension(nvara) var_aname
Definition mod_netcdf.F:181
subroutine, public netcdf_inq_var(ng, model, ncname, ncid, myvarname, searchvar, varid, nvardim, nvaratt)
logical master
subroutine, public pio_netcdf_inq_var(ng, model, ncname, piofile, myvarname, searchvar, piovar, nvardim, nvaratt)
subroutine, public pio_netcdf_close(ng, model, piofile, ncname, lupdate)
subroutine, public pio_netcdf_open(ng, model, ncname, omode, piofile)
type(t_clock) rclock
integer exit_flag
integer noerror
character(len(sinp)) function, public lowercase(sinp)
Definition strings.F:531
logical function, public founderror(flag, noerr, line, routine)
Definition strings.F:52

References mod_scalars::exit_flag, strings_mod::founderror(), mod_ncparam::io_nf90, mod_ncparam::io_pio, strings_mod::lowercase(), mod_parallel::master, mod_netcdf::n_var, mod_netcdf::netcdf_close(), mod_netcdf::netcdf_inq_var(), mod_netcdf::netcdf_open(), mod_scalars::noerror, mod_pio_netcdf::pio_netcdf_close(), mod_pio_netcdf::pio_netcdf_inq_var(), mod_pio_netcdf::pio_netcdf_open(), mod_scalars::rclock, mod_iounits::sourcefile, mod_iounits::stdout, mod_netcdf::var_achar, mod_netcdf::var_aname, mod_netcdf::var_dsize, mod_netcdf::var_name, and mod_netcdf::var_ndim.

Here is the call graph for this function:

◆ check_multifile()

subroutine check_multifile ( integer, intent(in) ng,
integer, intent(in) model )

Definition at line 2 of file check_multifile.F.

3!
4!git $Id$
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2025 The ROMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.md !
9!=======================================================================
10! !
11! If applicable, this routine checks input NetCDF multi-files and !
12! sets several parameters in the file information structure so the !
13! appropriate file is selected during initialization or restart. !
14! !
15! Multi-files are allowed for several input fields. That is, the !
16! time records for a particular input field can be split into !
17! several NetCDF files. !
18! !
19!=======================================================================
20!
21 USE mod_param
22 USE mod_iounits
23 USE mod_ncparam
24 USE mod_scalars
25!
26 USE dateclock_mod, ONLY : time_string
27 USE strings_mod, ONLY : founderror
28!
29 implicit none
30!
31! Imported variable declarations.
32!
33 integer, intent(in) :: ng, model
34!
35! Local variable declarations.
36!
37 integer :: i, max_files
38!
39 real(dp) :: Tfinal
40!
41 character (len= 1), parameter :: blank = ' '
42 character (len=40) :: file_type
43!
44 character (len=*), parameter :: MyFile = &
45 & __FILE__
46!
47 sourcefile=myfile
48!
49!=======================================================================
50! If applicable, initialize parameters for input multi-files.
51!=======================================================================
52!
53! Initialize I/O information variables to facilitate to reset the
54! values in iterative algorithms that call the NLM, TLM, RPM, and
55! ADM kernels repetitevely. Notice that Iinfo(1,:,:) is not reset
56! because it is part of the metadata.
57!
58 DO i=1,nv
59 cinfo(i,ng)=blank
60 linfo(1,i,ng)=.false.
61 linfo(2,i,ng)=.false.
62 linfo(3,i,ng)=.false.
63 linfo(4,i,ng)=.false.
64 linfo(5,i,ng)=.false.
65 linfo(6,i,ng)=.false.
66 iinfo(2,i,ng)=-1
67 iinfo(3,i,ng)=-1
68 iinfo(4,i,ng)=0
69 iinfo(5,i,ng)=0
70 iinfo(6,i,ng)=0
71 iinfo(7,i,ng)=0
72 iinfo(8,i,ng)=2
73 iinfo(9,i,ng)=0
74 iinfo(10,i,ng)=0
75 finfo(1,i,ng)=0.0_r8
76 finfo(2,i,ng)=0.0_r8
77 finfo(3,i,ng)=0.0_r8
78 finfo(5,i,ng)=0.0_r8
79 finfo(6,i,ng)=0.0_r8
80 finfo(7,i,ng)=0.0_r8
81 finfo(10,i,ng)=1.0_r8
82 fpoint(1,i,ng)=0.0_r8
83 fpoint(2,i,ng)=0.0_r8
84 tintrp(1,i,ng)=0.0_r8
85 tintrp(2,i,ng)=0.0_r8
86 vtime(1,i,ng)=0.0_r8
87 vtime(2,i,ng)=0.0_r8
88 frcncid(i,ng)=-1
89 END DO
90!
91! Get initialization time string.
92!
93 CALL time_string (time(ng), i_code)
94!
95! Get final time string for simulation.
96!
97 IF (model.eq.iadm) THEN
98 tfinal=time(ng)-ntimes(ng)*dt(ng)
99 ELSE
100 tfinal=time(ng)+ntimes(ng)*dt(ng)
101 END IF
102 CALL time_string (tfinal, f_code)
103!
104!-----------------------------------------------------------------------
105! Input lateral boundary conditions data.
106!-----------------------------------------------------------------------
107!
108 IF (obcdata(ng)) THEN
109 file_type='Lateral Boundary'
110 max_files=nbcfiles(ng)
111 CALL multifile_info_s2d (ng, model, file_type, nbcfiles, &
112 & max_files, bry)
113 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
114 END IF
115!
116!-----------------------------------------------------------------------
117! Input climatology data.
118!-----------------------------------------------------------------------
119!
120 IF (clm_file(ng)) THEN
121 file_type='Climatology'
122 max_files=nclmfiles(ng)
123 CALL multifile_info_s2d (ng, model, file_type, nclmfiles, &
124 & max_files, clm)
125 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
126 END IF
127
128#ifdef FORWARD_READ
129!
130!-----------------------------------------------------------------------
131! Nonlinear model forward trajectory data.
132!-----------------------------------------------------------------------
133!
134 IF (lreadfwd(ng)) THEN
135 CALL multifile_info_s1d (ng, model, 'Forward', fwd)
136 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
137 END IF
138#endif
139
140#if defined TANGENT || defined TL_IOMS
141!
142!-----------------------------------------------------------------------
143! Adjoint model trajectory data.
144!-----------------------------------------------------------------------
145!
146 IF (lreadtlm(ng)) THEN
147 CALL multifile_info_s1d (ng, model, 'Tangent Linear', tlm)
148 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
149 END IF
150#endif
151
152#ifdef FORWARD_FLUXES
153!
154!-----------------------------------------------------------------------
155! Nonlinear model surface fluxes data.
156!-----------------------------------------------------------------------
157!
158 IF (lreadblk(ng)) THEN
159 CALL multifile_info_s1d (ng, model, 'Nonlinear Fluxes', blk)
160 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
161 END IF
162#endif
163
164#ifndef ANA_PSOURCE
165!
166!-----------------------------------------------------------------------
167! Input Source/Sink data (river runoff).
168!-----------------------------------------------------------------------
169!
170 IF (luvsrc(ng).or.lwsrc(ng)) THEN
171 file_type='Sources/Sinks Data'
172 CALL multifile_info_s1d (ng, model, file_type, ssf)
173 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
174 END IF
175#endif
176
177#ifdef FRC_FILE
178!
179!-----------------------------------------------------------------------
180! Input forcing data.
181!-----------------------------------------------------------------------
182!
183 IF (lreadfrc(ng)) THEN
184 file_type='Forcing'
185 max_files=maxval(nffiles)
186 CALL multifile_info_s2d (ng, model, file_type, nffiles, &
187 & max_files, frc)
188 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
189 END IF
190#endif
191!
192 RETURN
subroutine multifile_info_s1d(ng, model, file_type, s)
subroutine multifile_info_s2d(ng, model, file_type, inpfiles, idim, s)
subroutine, public time_string(mytime, date_string)
Definition dateclock.F:1272
type(t_io), dimension(:), allocatable ssf
integer, dimension(:), allocatable nclmfiles
type(t_io), dimension(:), allocatable tlm
type(t_io), dimension(:), allocatable blk
type(t_io), dimension(:,:), allocatable frc
type(t_io), dimension(:,:), allocatable bry
type(t_io), dimension(:), allocatable fwd
integer, dimension(:), allocatable nbcfiles
type(t_io), dimension(:,:), allocatable clm
integer, dimension(:), allocatable nffiles
character(len=256), dimension(:,:), allocatable cinfo
integer, parameter nv
logical, dimension(:,:,:), allocatable linfo
real(dp), dimension(:,:,:), allocatable vtime
integer, dimension(:,:), allocatable frcncid
real(dp), dimension(:,:,:), allocatable tintrp
real(dp), dimension(:,:,:), allocatable fpoint
real(dp), dimension(:,:,:), allocatable finfo
integer, dimension(:,:,:), allocatable iinfo
integer, parameter iadm
Definition mod_param.F:665
logical, dimension(:), allocatable clm_file
logical, dimension(:), allocatable luvsrc
integer, dimension(:), allocatable ntimes
real(dp), dimension(:), allocatable dt
logical, dimension(:), allocatable lreadfrc
logical, dimension(:), allocatable lwsrc
character(len=22) i_code
logical, dimension(:), allocatable obcdata
logical, dimension(:), allocatable lreadtlm
real(dp), dimension(:), allocatable time
logical, dimension(:), allocatable lreadfwd
logical, dimension(:), allocatable lreadblk
character(len=22) f_code

References mod_iounits::blk, mod_iounits::bry, mod_ncparam::cinfo, mod_iounits::clm, mod_scalars::clm_file, mod_scalars::dt, mod_scalars::exit_flag, mod_scalars::f_code, mod_ncparam::finfo, strings_mod::founderror(), mod_ncparam::fpoint, mod_iounits::frc, mod_ncparam::frcncid, mod_iounits::fwd, mod_scalars::i_code, mod_param::iadm, mod_ncparam::iinfo, mod_ncparam::linfo, mod_scalars::lreadblk, mod_scalars::lreadfrc, mod_scalars::lreadfwd, mod_scalars::lreadtlm, mod_scalars::luvsrc, mod_scalars::lwsrc, multifile_info_s1d(), multifile_info_s2d(), mod_iounits::nbcfiles, mod_iounits::nclmfiles, mod_iounits::nffiles, mod_scalars::noerror, mod_scalars::ntimes, mod_ncparam::nv, mod_scalars::obcdata, mod_iounits::sourcefile, mod_iounits::ssf, mod_scalars::time, dateclock_mod::time_string(), mod_ncparam::tintrp, mod_iounits::tlm, and mod_ncparam::vtime.

Referenced by ad_initial(), roms_kernel_mod::adm_initial(), initial(), roms_kernel_mod::nlm_initial(), rp_initial(), tl_initial(), and roms_kernel_mod::tlm_initial().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ multifile_info_s1d()

subroutine multifile_info_s1d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) file_type,
type(t_io), dimension(ngrids), intent(inout) s )

Definition at line 195 of file check_multifile.F.

196!
197!=======================================================================
198! !
199! Updates multi-file information for the given 1D file structure, S. !
200! !
201! On Input: !
202! !
203! ng Nested grid number (integer) !
204! model Calling model identifier (integer) !
205! file_type File structure indentifier (string) !
206! S 2D Derived type structure, TYPE(T_IO) !
207! !
208!=======================================================================
209!
210 USE mod_param
211 USE mod_parallel
212 USE mod_iounits
213 USE mod_ncparam
214 USE mod_scalars
215!
216 USE dateclock_mod, ONLY : time_string
217 USE strings_mod, ONLY : founderror, lowercase
218!
219! Imported variable declarations.
220!
221 integer, intent(in) :: ng, model
222!
223 character (len=*), intent(in) :: file_type
224!
225 TYPE(T_IO), intent(inout) :: S(Ngrids)
226!
227! Local variable declarations.
228!
229 logical :: Lcheck, foundit
230 logical :: check_file
231!
232 integer :: Fcount, Nfiles, i, ifile
233!
234 real(dp) :: Tfinal, Tmax, Tmin, Tscale
235!
236 character (len= 22) :: Tmin_code, Tmax_code
237 character (len=256) :: ncname
238
239 character (len=*), parameter :: MyFile = &
240 & __FILE__//", multifile_info_s1d"
241!
242 sourcefile=myfile
243!
244!-----------------------------------------------------------------------
245! Update file structure parameters.
246!-----------------------------------------------------------------------
247!
248! Set final time of simulation.
249!
250 IF (model.eq.iadm) THEN
251 tfinal=time(ng)-ntimes(ng)*dt(ng)
252 ELSE
253 tfinal=time(ng)+ntimes(ng)*dt(ng)
254 END IF
255!
256! Set minimum and maximum time values.
257!
258 nfiles=s(ng)%Nfiles
259 DO ifile=1,nfiles
260 ncname=trim(s(ng)%files(ifile))
261 foundit=check_file(ng, model, nfiles, ncname, s(ng)%IOtype, &
262 & tmin, tmax, tscale, lcheck)
263 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
264 s(ng)%time_min(ifile)=tmin
265 s(ng)%time_max(ifile)=tmax
266 END DO
267!
268! Set the appropriate file counter to use during initialization or
269! restart.
270!
271 fcount=0
272 IF (lcheck) THEN
273 IF (model.eq.iadm) THEN
274 DO ifile=nfiles,1,-1
275 tmax=tscale*s(ng)%time_max(ifile)
276 IF (time(ng).le.tmax) THEN
277 fcount=ifile
278 END IF
279 END DO
280 ELSE
281 DO ifile=1,nfiles
282 tmin=tscale*s(ng)%time_min(ifile)
283 IF (time(ng).ge.tmin) THEN
284 fcount=ifile
285 END IF
286 END DO
287 END IF
288 ELSE
289 fcount=1
290 END IF
291!
292! Initialize other structure parameters or issue an error if data does
293! not include initalization time.
294!
295 IF (fcount.gt.0) THEN
296 s(ng)%Fcount=fcount
297 ncname=s(ng)%files(fcount)
298 s(ng)%name=trim(ncname)
299 ELSE
300 IF (master.and.lcheck) THEN
301 WRITE (stdout,10) trim(lowercase(file_type)), i_code
302 DO ifile=1,nfiles
303 tmin=tscale*s(ng)%time_min(ifile)
304 tmax=tscale*s(ng)%time_max(ifile)
305 CALL time_string (tmin, tmin_code)
306 CALL time_string (tmax, tmax_code)
307 WRITE (stdout,20) tmin_code, tmax_code, &
308 & trim(s(ng)%files(ifile))
309 END DO
310 END IF
311 exit_flag=4
312 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
313 END IF
314!
315! Check if there is data up to the end of the simulation.
316!
317 IF (lcheck) THEN
318 IF (model.eq.iadm) THEN
319 tmin=tscale*s(ng)%time_min(1)
320 IF (tfinal.lt.tmin) THEN
321 CALL time_string (tmin, tmin_code)
322 IF (master) THEN
323 WRITE (stdout,30) trim(file_type)//' (adjoint)', &
324 & trim(s(ng)%files(1)), &
325 & 'first ', tmin_code, f_code
326 END IF
327 exit_flag=4
328 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
329 END IF
330 ELSE
331 tmax=tscale*s(ng)%time_max(nfiles)
332 IF (tfinal.gt.tmax) THEN
333 CALL time_string (tmax, tmax_code)
334 IF (master) THEN
335 WRITE (stdout,30) trim(file_type), &
336 & trim(s(ng)%files(nfiles)), &
337 & 'last ', tmax_code, f_code
338 END IF
339 exit_flag=4
341 & __line__, myfile)) RETURN
342 END IF
343 END IF
344 END IF
345!
346 10 FORMAT (/,' MULTIFILE_INFO_S1D - Error while processing ', a, &
347 & ' multi-files: ',/,22x,'data does not include', &
348 & ' initialization time = ', a,/)
349 20 FORMAT (3x,a,2x,a,5x,a)
350 30 FORMAT (/,' MULTIFILE_INFO_S1D - Error while checking input ', a, &
351 & ' file:',/,22x,a,/,22x, &
352 & a,'data time record available is for day: ',a,/,22x, &
353 & 'but data is needed to finish run until day: ',a)
354!
355 RETURN
logical function check_file(ng, model, nfiles, ncname, iotype, tmin, tmax, tscale, lcheck)

References mod_scalars::dt, mod_scalars::exit_flag, mod_scalars::f_code, strings_mod::founderror(), mod_scalars::i_code, mod_param::iadm, strings_mod::lowercase(), mod_parallel::master, mod_scalars::noerror, mod_scalars::ntimes, mod_iounits::sourcefile, mod_iounits::stdout, mod_scalars::time, and dateclock_mod::time_string().

Referenced by check_multifile().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ multifile_info_s2d()

subroutine multifile_info_s2d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) file_type,
integer, dimension(ngrids), intent(in) inpfiles,
integer, intent(in) idim,
type(t_io), dimension(idim,ngrids), intent(inout) s )

Definition at line 358 of file check_multifile.F.

360!
361!=======================================================================
362! !
363! Updates multi-file information for the given 2D file structure, S. !
364! !
365! On Input: !
366! !
367! ng Nested grid number (integer) !
368! model Calling model identifier (integer) !
369! file_type File structure indentifier (string) !
370! InpFiles Number of source input files per grid (integer vector)!
371! idim Size of structure inner dimension (integer): !
372! idim=MAXVAL(InpFiles) in calling routine !
373! S 2D Derived type structure, TYPE(T_IO) !
374! !
375!=======================================================================
376!
377 USE mod_param
378 USE mod_parallel
379 USE mod_iounits
380 USE mod_ncparam
381 USE mod_scalars
382!
383 USE dateclock_mod, ONLY : time_string
384 USE strings_mod, ONLY : founderror, lowercase
385!
386! Imported variable declarations.
387!
388 integer, intent(in) :: ng, model, idim
389 integer, intent(in) :: InpFiles(Ngrids)
390!
391 character (len=*), intent(in) :: file_type
392!
393 TYPE(T_IO), intent(inout) :: S(idim,Ngrids)
394!
395! Local variable declarations.
396!
397 logical :: Lcheck, foundit
398 logical :: check_file
399!
400 integer :: Fcount, Nfiles, i, ifile
401!
402 real(dp) :: Tfinal, Tmax, Tmin, Tscale
403!
404 character (len= 22) :: Tmin_code, Tmax_code
405 character (len=256) :: ncname
406
407 character (len=*), parameter :: MyFile = &
408 & __FILE__//", multifile_info_s2d"
409!
410 sourcefile=myfile
411!
412!-----------------------------------------------------------------------
413! Update file structure parameters.
414!-----------------------------------------------------------------------
415!
416! Set final time of simulation.
417!
418 IF (model.eq.iadm) THEN
419 tfinal=time(ng)-ntimes(ng)*dt(ng)
420 ELSE
421 tfinal=time(ng)+ntimes(ng)*dt(ng)
422 END IF
423!
424! Set minimum and maximum time values.
425!
426 DO i=1,inpfiles(ng)
427 nfiles=s(i,ng)%Nfiles
428 DO ifile=1,nfiles
429 ncname=trim(s(i,ng)%files(ifile))
430 foundit=check_file(ng, model, nfiles, ncname, s(i,ng)%IOtype, &
431 & tmin, tmax, tscale, lcheck)
432 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
433 s(i,ng)%time_min(ifile)=tmin
434 s(i,ng)%time_max(ifile)=tmax
435 END DO
436!
437! Set the appropriate file counter to use during initialization or
438! restart.
439!
440 fcount=0
441 IF (lcheck) THEN
442 IF (model.eq.iadm) THEN
443 DO ifile=nfiles,1,-1
444 tmax=tscale*s(i,ng)%time_max(ifile)
445 IF (time(ng).le.tmax) THEN
446 fcount=ifile
447 END IF
448 END DO
449 ELSE
450 DO ifile=1,nfiles
451 tmin=tscale*s(i,ng)%time_min(ifile)
452 IF (time(ng).ge.tmin) THEN
453 fcount=ifile
454 END IF
455 END DO
456 END IF
457 ELSE
458 fcount=1
459 END IF
460!
461! Initialize other structure parameters or issue an error if data does
462! not include initalization time.
463!
464 IF (fcount.gt.0) THEN
465 s(i,ng)%Fcount=fcount
466 ncname=s(i,ng)%files(fcount)
467 s(i,ng)%name=trim(ncname)
468 ELSE
469 IF (master.and.lcheck) THEN
470 WRITE (stdout,10) trim(lowercase(file_type)), i_code
471 DO ifile=1,nfiles
472 tmin=tscale*s(i,ng)%time_min(ifile)
473 tmax=tscale*s(i,ng)%time_max(ifile)
474 CALL time_string (tmin, tmin_code)
475 CALL time_string (tmax, tmax_code)
476 WRITE (stdout,20) tmin_code, tmax_code, &
477 & trim(s(i,ng)%files(ifile))
478 END DO
479 END IF
480 exit_flag=4
481 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
482 END IF
483!
484! Check if there is data up to the end of the simulation.
485!
486 IF (lcheck) THEN
487 IF (model.eq.iadm) THEN
488 tmin=tscale*s(i,ng)%time_min(1)
489 IF (tfinal.lt.tmin) THEN
490 CALL time_string (tmin, tmin_code)
491 IF (master) THEN
492 WRITE (stdout,30) trim(file_type)//' (adjoint)', &
493 & trim(s(i,ng)%files(1)), &
494 & 'first ', tmin_code, f_code
495 END IF
496 exit_flag=4
498 & __line__, myfile)) RETURN
499 END IF
500 ELSE
501 tmax=tscale*s(i,ng)%time_max(nfiles)
502 IF (tfinal.gt.tmax) THEN
503 CALL time_string (tmax, tmax_code)
504 IF (master) THEN
505 WRITE (stdout,30) trim(file_type), &
506 & trim(s(i,ng)%files(nfiles)), &
507 & 'last ', tmax_code, f_code
508 END IF
509 exit_flag=4
511 & __line__, myfile)) RETURN
512 END IF
513 END IF
514 END IF
515 END DO
516!
517 10 FORMAT (/,' MULTIFILE_INFO_S2D - Error while processing ', a, &
518 & ' multi-files: ',/,22x,'data does not include', &
519 & ' initialization time = ', a,/)
520 20 FORMAT (3x,a,2x,a,5x,a)
521 30 FORMAT (/,' MULTIFILE_INFO_S2D - Error while checking input ', a, &
522 & ' file:',/,22x,a,/,22x, &
523 & a,'data time record available is for day: ',a,/,22x, &
524 & 'but data is needed to finish run until day: ',a)
525!
526 RETURN

References mod_scalars::dt, mod_scalars::exit_flag, mod_scalars::f_code, strings_mod::founderror(), mod_scalars::i_code, mod_param::iadm, strings_mod::lowercase(), mod_parallel::master, mod_scalars::noerror, mod_scalars::ntimes, mod_iounits::sourcefile, mod_iounits::stdout, mod_scalars::time, and dateclock_mod::time_string().

Referenced by check_multifile().

Here is the call graph for this function:
Here is the caller graph for this function: