MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
listreadermodule Module Reference

Generic List Reader Module.

Data Types

type  listreadertype
 

Functions/Subroutines

subroutine read_list (this, line_reader, in, iout, nlist, inamedbound, mshape, nodelist, rlist, auxvar, auxname, boundname, label)
 Initialize the reader. More...
 
subroutine read_control_record (this)
 Check for a control record, and parse if found. More...
 
subroutine set_openclose (this)
 Set up for open/close file. More...
 
subroutine read_data (this)
 Read the data. More...
 
subroutine read_binary (this)
 Read the data from a binary file. More...
 
subroutine read_ascii (this)
 Read the data from an ascii file. More...
 
subroutine check_cellid (ii, cellid, mshape, ndim)
 Check for valid cellid. More...
 
subroutine write_list (this)
 Write input data to a list. More...
 

Function/Subroutine Documentation

◆ check_cellid()

subroutine listreadermodule::check_cellid ( integer(i4b), intent(in)  ii,
integer(i4b), dimension(:), intent(in)  cellid,
integer(i4b), dimension(:), intent(in)  mshape,
integer(i4b), intent(in)  ndim 
)
Parameters
[in]mshapemodel shape
[in]ndimsize of mshape

Definition at line 538 of file ListReader.f90.

539  ! -- dummy
540  integer(I4B), intent(in) :: ii
541  integer(I4B), dimension(:), intent(in) :: cellid !< cellid
542  integer(I4B), dimension(:), intent(in) :: mshape !< model shape
543  integer(I4B), intent(in) :: ndim !< size of mshape
544  ! -- local
545  character(len=20) :: cellstr, mshstr
546  ! -- formats
547  character(len=*), parameter :: fmterr = &
548  "('List entry ',i0,' contains cellid ',a,' but this cellid is invalid &
549  &for model with shape ', a)"
550  character(len=*), parameter :: fmtndim1 = &
551  "('(',i0,')')"
552  character(len=*), parameter :: fmtndim2 = &
553  "('(',i0,',',i0,')')"
554  character(len=*), parameter :: fmtndim3 = &
555  "('(',i0,',',i0,',',i0,')')"
556  !
557  if (ndim == 1) then
558  if (cellid(1) < 1 .or. cellid(1) > mshape(1)) then
559  write (cellstr, fmtndim1) cellid(1)
560  write (mshstr, fmtndim1) mshape(1)
561  write (errmsg, fmterr) ii, trim(adjustl(cellstr)), trim(adjustl(mshstr))
562  call store_error(errmsg)
563  end if
564  else if (ndim == 2) then
565  if (cellid(1) < 1 .or. cellid(1) > mshape(1) .or. &
566  cellid(2) < 1 .or. cellid(2) > mshape(2)) then
567  write (cellstr, fmtndim2) cellid(1), cellid(2)
568  write (mshstr, fmtndim2) mshape(1), mshape(2)
569  write (errmsg, fmterr) ii, trim(adjustl(cellstr)), trim(adjustl(mshstr))
570  call store_error(errmsg)
571  end if
572  else if (ndim == 3) then
573  if (cellid(1) < 1 .or. cellid(1) > mshape(1) .or. &
574  cellid(2) < 1 .or. cellid(2) > mshape(2) .or. &
575  cellid(3) < 1 .or. cellid(3) > mshape(3)) then
576  write (cellstr, fmtndim3) cellid(1), cellid(2), cellid(3)
577  write (mshstr, fmtndim3) mshape(1), mshape(2), mshape(3)
578  write (errmsg, fmterr) ii, trim(adjustl(cellstr)), trim(adjustl(mshstr))
579  call store_error(errmsg)
580  end if
581  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ read_ascii()

subroutine listreadermodule::read_ascii ( class(listreadertype this)

Definition at line 356 of file ListReader.f90.

357  ! -- modules
359  use inputoutputmodule, only: urword
361  use tdismodule, only: kper
362  ! -- dummy
363  class(ListReaderType) :: this
364  ! -- local
365  integer(I4B) :: mxlist, ldim, naux
366  integer(I4B) :: ii, jj, idum, nod, istat, increment
367  real(DP) :: r
368  integer(I4B), dimension(:), allocatable :: cellid
369  character(len=LINELENGTH) :: fname
370  ! -- formats
371  character(len=*), parameter :: fmtmxlsterronly = &
372  "('Error reading list. The number of records encountered exceeds &
373  &the maximum number of records. Number of records found is ',I0,&
374  &' but MAXBOUND is ', I0, '. Try increasing MAXBOUND for this list. &
375  &Error occurred reading the following line: ', a, 5x, '>>> ', a)"
376  !
377  ! -- Determine array sizes
378  mxlist = size(this%rlist, 2)
379  ldim = size(this%rlist, 1)
380  naux = size(this%auxvar, 1)
381  this%ntxtrlist = 0
382  this%ntxtauxvar = 0
383  !
384  ! -- Allocate arrays
385  allocate (cellid(this%ndim))
386  !
387  ii = 1
388  readloop: do
389  !
390  ! -- First line was already read, so don't read again
391  if (ii /= 1) &
392  call this%line_reader%rdcom(this%inlist, 0, this%line, this%ierr)
393  !
394  ! -- If this is an unknown-length list, then check for END.
395  ! If found, then backspace, set nlist, and exit readloop.
396  if (this%nlist < 0) then
397  this%lloc = 1
398  call urword(this%line, this%lloc, this%istart, this%istop, 1, idum, r, &
399  this%iout, this%inlist)
400  if (this%line(this%istart:this%istop) == 'END' .or. this%ierr < 0) then
401  ! -- If END was found then call line_reader backspace
402  ! emulator so that caller can proceed with reading END.
403  if (this%ierr == 0) then
404  call this%line_reader%bkspc(this%inlist)
405  end if
406  this%nlist = ii - 1
407  exit readloop
408  end if
409  end if
410  !
411  ! -- Check range
412  if (ii > mxlist) then
413  inquire (unit=this%inlist, name=fname)
414  write (errmsg, fmtmxlsterronly) &
415  ii, mxlist, new_line("A"), trim(this%line)
416  call store_error(errmsg)
417  call store_error_unit(this%inlist)
418  end if
419  !
420  ! -- Initialize locator
421  this%lloc = 1
422  !
423  ! -- Read cellid
424  call urword(this%line, this%lloc, this%istart, this%istop, 2, &
425  cellid(1), r, this%iout, this%inlist)
426  if (this%ndim > 1) then
427  call urword(this%line, this%lloc, this%istart, this%istop, 2, &
428  cellid(2), r, this%iout, this%inlist)
429  end if
430  if (this%ndim > 2) then
431  call urword(this%line, this%lloc, this%istart, this%istop, 2, &
432  cellid(3), r, this%iout, this%inlist)
433  end if
434  !
435  ! -- Ensure cellid is valid, store an error otherwise
436  call check_cellid(ii, cellid, this%mshape, this%ndim)
437  !
438  ! -- Calculate user node number
439  if (this%ndim == 3) then
440  nod = get_node(cellid(1), cellid(2), cellid(3), &
441  this%mshape(1), this%mshape(2), this%mshape(3))
442  elseif (this%ndim == 2) then
443  nod = get_node(cellid(1), 1, cellid(2), &
444  this%mshape(1), 1, this%mshape(2))
445  else
446  nod = cellid(1)
447  end if
448  !
449  ! -- Assign nod to nodelist
450  this%nodelist(ii) = nod
451  !
452  ! -- Read rlist
453  do jj = 1, ldim
454  call urword(this%line, this%lloc, this%istart, this%istop, 0, idum, &
455  r, this%iout, this%inlist)
456  read (this%line(this%istart:this%istop), *, iostat=istat) r
457  !
458  ! -- If a double precision value, then store in rlist, otherwise store
459  ! the text name and location
460  if (istat == 0) then
461  this%rlist(jj, ii) = r
462  else
463  this%rlist(jj, ii) = dzero
464  this%ntxtrlist = this%ntxtrlist + 1
465  if (this%ntxtrlist > size(this%txtrlist)) then
466  increment = int(size(this%txtrlist) * 0.2)
467  increment = max(100, increment)
468  call expandarray(this%txtrlist, increment)
469  call expandarray(this%idxtxtrow, increment)
470  call expandarray(this%idxtxtcol, increment)
471  end if
472  this%txtrlist(this%ntxtrlist) = this%line(this%istart:this%istop)
473  this%idxtxtrow(this%ntxtrlist) = ii
474  this%idxtxtcol(this%ntxtrlist) = jj
475  end if
476  !
477  end do
478  !
479  ! -- Read auxvar
480  do jj = 1, naux
481  call urword(this%line, this%lloc, this%istart, this%istop, 0, idum, &
482  r, this%iout, this%inlist)
483  read (this%line(this%istart:this%istop), *, iostat=istat) r
484  !
485  ! -- If a double precision value, then store in auxvar, otherwise store
486  ! the text name and location
487  if (istat == 0) then
488  this%auxvar(jj, ii) = r
489  else
490  this%auxvar(jj, ii) = dzero
491  this%ntxtauxvar = this%ntxtauxvar + 1
492  if (this%ntxtauxvar > size(this%txtauxvar)) then
493  increment = int(size(this%txtauxvar) * 0.2)
494  increment = max(100, increment)
495  call expandarray(this%txtauxvar, increment)
496  call expandarray(this%idxtxtauxrow, increment)
497  call expandarray(this%idxtxtauxcol, increment)
498  end if
499  this%txtauxvar(this%ntxtauxvar) = this%line(this%istart:this%istop)
500  this%idxtxtauxrow(this%ntxtauxvar) = ii
501  this%idxtxtauxcol(this%ntxtauxvar) = jj
502  if (len_trim(this%txtauxvar(this%ntxtauxvar)) == 0) then
503  write (errmsg, '(a,i0,a)') 'Auxiliary data or time series name &
504  &expected but not found in period &
505  &block "', kper, '".'
506  call store_error(errmsg)
507  call store_error_unit(this%inlist)
508  end if
509  end if
510  !
511  end do
512  !
513  ! -- Read the boundary names (only supported for ascii input)
514  if (this%inamedbound > 0) then
515  call urword(this%line, this%lloc, this%istart, this%istop, 1, idum, r, &
516  this%iout, this%inlist)
517  this%boundname(ii) = this%line(this%istart:this%istop)
518  end if
519  !
520  ! -- If nlist is known, then exit when nlist values have been read
521  if (this%nlist > 0) then
522  if (ii == this%nlist) exit readloop
523  end if
524  !
525  ! -- Increment ii row counter
526  ii = ii + 1
527  !
528  end do readloop
529  !
530  ! -- Stop if errors were detected
531  if (count_errors() > 0) then
532  call store_error_unit(this%inlist)
533  end if
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:36
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
Here is the call graph for this function:

◆ read_binary()

subroutine listreadermodule::read_binary ( class(listreadertype this)
private

Definition at line 253 of file ListReader.f90.

254  ! -- modules
256  ! -- dummy
257  class(ListReaderType) :: this
258  ! -- local
259  integer(I4B) :: mxlist, ldim, naux, nod, ii, jj
260  character(len=LINELENGTH) :: fname
261  integer(I4B), dimension(:), allocatable :: cellid
262  ! -- formats
263  character(len=*), parameter :: fmtmxlsterronly = &
264  "('ERROR READING LIST FROM FILE: ',&
265  &a,' ON UNIT: ',I0,&
266  &' THE NUMBER OF RECORDS ENCOUNTERED EXCEEDS THE MAXIMUM NUMBER &
267  &OF RECORDS. TRY INCREASING MAXBOUND FOR THIS LIST.&
268  & NUMBER OF RECORDS: ',I0,' MAXBOUND: ',I0)"
269  character(len=*), parameter :: fmtlsterronly = &
270  "('ERROR READING LIST FROM FILE: ',&
271  &1x,a,1x,' ON UNIT: ',I0)"
272  !
273  ! -- Determine array sizes
274  mxlist = size(this%rlist, 2)
275  ldim = size(this%rlist, 1)
276  naux = size(this%auxvar, 1)
277  !
278  ! -- Allocate arrays
279  allocate (cellid(this%ndim))
280  !
281  ii = 1
282  readloop: do
283  !
284  ! -- Read layer, row, col, or cell number
285  read (this%inlist, iostat=this%ierr) cellid
286  !
287  ! -- If not end of record, then store nodenumber, else
288  ! calculate lstend and nlist, and exit readloop
289  select case (this%ierr)
290  case (0)
291  !
292  ! -- Ensure cellid is valid, store an error otherwise
293  call check_cellid(ii, cellid, this%mshape, this%ndim)
294  !
295  ! -- Check range
296  if (ii > mxlist) then
297  inquire (unit=this%inlist, name=fname)
298  write (errmsg, fmtmxlsterronly) fname, this%inlist, ii, mxlist
299  call store_error(errmsg, terminate=.true.)
300  end if
301  !
302  ! -- Calculate and store user node number
303  if (this%ndim == 1) then
304  nod = cellid(1)
305  elseif (this%ndim == 2) then
306  nod = get_node(cellid(1), 1, cellid(2), &
307  this%mshape(1), 1, this%mshape(2))
308  else
309  nod = get_node(cellid(1), cellid(2), cellid(3), &
310  this%mshape(1), this%mshape(2), this%mshape(3))
311  end if
312  this%nodelist(ii) = nod
313  !
314  ! -- Read remainder of record
315  read (this%inlist, iostat=this%ierr) (this%rlist(jj, ii), jj=1, ldim), &
316  (this%auxvar(jj, ii), jj=1, naux)
317  if (this%ierr /= 0) then
318  inquire (unit=this%inlist, name=fname)
319  write (errmsg, fmtlsterronly) trim(adjustl(fname)), this%inlist
320  call store_error(errmsg, terminate=.true.)
321  end if
322  !
323  case (:-1)
324  !
325  ! -- End of record was encountered
326  this%nlist = ii - 1
327  exit readloop
328  !
329  case (1:)
330  !
331  ! -- Error
332  inquire (unit=this%inlist, name=fname)
333  write (errmsg, fmtlsterronly) trim(adjustl(fname)), this%inlist
334  call store_error(errmsg, terminate=.true.)
335  !
336  end select
337  !
338  ! -- If nlist is known, then exit when nlist values have been read
339  if (this%nlist > 0) then
340  if (ii == this%nlist) exit readloop
341  end if
342  !
343  ! -- Increment ii
344  ii = ii + 1
345  !
346  end do readloop
347  !
348  ! -- Stop if errors were detected
349  if (count_errors() > 0) then
350  call store_error_unit(this%inlist)
351  end if
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
Here is the call graph for this function:

◆ read_control_record()

subroutine listreadermodule::read_control_record ( class(listreadertype this)

Definition at line 122 of file ListReader.f90.

123  ! -- modules
124  use inputoutputmodule, only: urword
125  ! -- dummy
126  class(ListReaderType) :: this
127  ! -- local
128  integer(I4B) :: idum
129  real(DP) :: r
130  ! -- formats
131  character(len=*), parameter :: fmtlsf = &
132  "(1X,'LIST SCALING FACTOR=',1PG12.5)"
133  !
134  ! -- Set default values, which may be changed by control record
135  this%inlist = this%in
136  this%iclose = 0
137  this%ibinary = 0
138  !
139  ! -- Read to the first non-commented line
140  call this%line_reader%rdcom(this%in, this%iout, this%line, this%ierr)
141  this%lloc = 1
142  call urword(this%line, this%lloc, this%istart, this%istop, 1, idum, r, &
143  this%iout, this%in)
144  !
145  ! -- Parse record
146  select case (this%line(this%istart:this%istop))
147  case ('OPEN/CLOSE')
148  call this%set_openclose()
149  end select
Here is the call graph for this function:

◆ read_data()

subroutine listreadermodule::read_data ( class(listreadertype this)

Definition at line 234 of file ListReader.f90.

235  ! -- dummy
236  class(ListReaderType) :: this
237  !
238  ! -- Read the list
239  if (this%ibinary == 1) then
240  call this%read_binary()
241  else
242  call this%read_ascii()
243  end if
244  !
245  ! -- If open/close, then close file
246  if (this%iclose == 1) then
247  close (this%inlist)
248  end if

◆ read_list()

subroutine listreadermodule::read_list ( class(listreadertype this,
type(longlinereadertype), intent(inout), target  line_reader,
integer(i4b), intent(in)  in,
integer(i4b), intent(in)  iout,
integer(i4b), intent(inout)  nlist,
integer(i4b), intent(in)  inamedbound,
integer(i4b), dimension(:), intent(in), pointer, contiguous  mshape,
integer(i4b), dimension(:), intent(inout), pointer, contiguous  nodelist,
real(dp), dimension(:, :), intent(inout), pointer, contiguous  rlist,
real(dp), dimension(:, :), intent(inout), pointer, contiguous  auxvar,
character(len=lenauxname), dimension(:), intent(inout), target  auxname,
character(len=lenboundname), dimension(:), intent(inout), pointer, contiguous  boundname,
character(len=lenlistlabel), intent(in)  label 
)
private

Definition at line 64 of file ListReader.f90.

67  ! -- modules
68  use constantsmodule, only: lenboundname
69  ! -- dummy
70  class(ListReaderType) :: this
71  type(LongLineReaderType), intent(inout), target :: line_reader
72  integer(I4B), intent(in) :: in
73  integer(I4B), intent(in) :: iout
74  integer(I4B), intent(inout) :: nlist
75  integer(I4B), intent(in) :: inamedbound
76  integer(I4B), dimension(:), intent(in), contiguous, pointer :: mshape
77  integer(I4B), dimension(:), intent(inout), contiguous, pointer :: nodelist
78  real(DP), dimension(:, :), intent(inout), contiguous, pointer :: rlist
79  real(DP), dimension(:, :), intent(inout), contiguous, pointer :: auxvar
80  character(len=LENAUXNAME), dimension(:), intent(inout), target :: auxname
81  character(len=LENBOUNDNAME), &
82  dimension(:), pointer, contiguous, intent(inout) :: boundname
83  character(len=LENLISTLABEL), intent(in) :: label
84  !
85  ! -- Copy variables
86  this%in = in
87  this%iout = iout
88  this%nlist = nlist
89  this%inamedbound = inamedbound
90  this%ndim = size(mshape)
91  this%label = label
92  !
93  ! -- Set pointers
94  this%mshape => mshape
95  this%nodelist => nodelist
96  this%rlist => rlist
97  this%auxvar => auxvar
98  this%auxname => auxname
99  this%boundname => boundname
100  this%line_reader => line_reader
101  !
102  ! -- Allocate arrays for storing text and text locations
103  if (.not. allocated(this%idxtxtrow)) allocate (this%idxtxtrow(0))
104  if (.not. allocated(this%idxtxtcol)) allocate (this%idxtxtcol(0))
105  if (.not. allocated(this%idxtxtauxrow)) allocate (this%idxtxtauxrow(0))
106  if (.not. allocated(this%idxtxtauxcol)) allocate (this%idxtxtauxcol(0))
107  if (.not. allocated(this%txtrlist)) allocate (this%txtrlist(0))
108  if (.not. allocated(this%txtauxvar)) allocate (this%txtauxvar(0))
109  !
110  ! -- Read control record
111  call this%read_control_record()
112  !
113  ! -- Read data
114  call this%read_data()
115  !
116  ! -- Set nlist for return
117  nlist = this%nlist

◆ set_openclose()

subroutine listreadermodule::set_openclose ( class(listreadertype this)

OPEN/CLOSE fname [(BINARY)]

Definition at line 156 of file ListReader.f90.

157  ! -- modules
158  use inputoutputmodule, only: urword, openfile
159  use openspecmodule, only: form, access
160  use constantsmodule, only: linelength
161  ! -- dummy
162  class(ListReaderType) :: this
163  ! -- local
164  integer(I4B) :: idum, itmp
165  real(DP) :: r
166  logical :: exists
167  integer(I4B) :: nunopn = 99
168  character(len=LINELENGTH) :: fname
169  ! -- formats
170  character(len=*), parameter :: fmtocne = &
171  &"('Specified OPEN/CLOSE file ',(A),' does not exist')"
172  character(len=*), parameter :: fmtobf = &
173  &"(1X,/1X,'OPENING BINARY FILE ON UNIT ',I0,':',/1X,A)"
174  character(len=*), parameter :: fmtobfnlist = &
175  &"(1X, 'TO READ ', I0, ' RECORDS.')"
176  character(len=*), parameter :: fmtofnlist = &
177  &"(1x,'TO READ ', I0, ' RECORDS.')"
178  character(len=*), parameter :: fmtof = &
179  &"(1X,/1X,'OPENING FILE ON UNIT ',I0,':',/1X,A)"
180  !
181  ! -- Get filename
182  call urword(this%line, this%lloc, this%istart, this%istop, 0, idum, r, &
183  this%iout, this%in)
184  fname = this%line(this%istart:this%istop)
185  !
186  ! -- Check to see if file OPEN/CLOSE file exists
187  inquire (file=fname, exist=exists)
188  if (.not. exists) then
189  write (errmsg, fmtocne) this%line(this%istart:this%istop)
190  call store_error(errmsg)
191  call store_error('Specified OPEN/CLOSE file does not exist')
192  call store_error_unit(this%in)
193  end if
194  !
195  ! -- Check for (BINARY) keyword
196  call urword(this%line, this%lloc, this%istart, this%istop, 1, idum, r, &
197  this%iout, this%in)
198  if (this%line(this%istart:this%istop) == '(BINARY)') this%ibinary = 1
199  !
200  ! -- Open the file depending on ibinary flag
201  this%inlist = nunopn
202  if (this%ibinary == 1) then
203  itmp = this%iout
204  if (this%iout > 0) then
205  itmp = 0
206  write (this%iout, fmtobf) this%inlist, trim(adjustl(fname))
207  if (this%nlist > 0) write (this%iout, fmtobfnlist) this%nlist
208  end if
209  call openfile(this%inlist, itmp, fname, 'OPEN/CLOSE', fmtarg_opt=form, &
210  accarg_opt=access)
211  else
212  itmp = this%iout
213  if (this%iout > 0) then
214  itmp = 0
215  write (this%iout, fmtof) this%inlist, trim(adjustl(fname))
216  if (this%nlist > 0) write (this%iout, fmtofnlist) this%nlist
217  end if
218  call openfile(this%inlist, itmp, fname, 'OPEN/CLOSE')
219  end if
220  !
221  ! -- Set iclose to 1 because it is open/close, to indicate that the
222  ! file needs to be closed after the list is read
223  this%iclose = 1
224  !
225  ! -- Read the first line from inlist to be consistent with how the list is
226  ! read when it is included in the package input file
227  if (this%ibinary /= 1) &
228  call this%line_reader%rdcom(this%inlist, this%iout, this%line, &
229  this%ierr)
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
Here is the call graph for this function:

◆ write_list()

subroutine listreadermodule::write_list ( class(listreadertype this)
private

Definition at line 586 of file ListReader.f90.

587  ! -- modules
590  use inputoutputmodule, only: ulstlb
591  use tablemodule, only: tabletype, table_cr
592  ! -- dummy
593  class(ListReaderType) :: this
594  ! -- local
595  character(len=10) :: cpos
596  character(len=LINELENGTH) :: tag
597  character(len=LINELENGTH), allocatable, dimension(:) :: words
598  integer(I4B) :: ntabrows
599  integer(I4B) :: ntabcols
600  integer(I4B) :: ipos
601  integer(I4B) :: ii, jj, i, j, k, nod
602  integer(I4B) :: ldim
603  integer(I4B) :: naux
604  type(TableType), pointer :: inputtab => null()
605  ! -- formats
606  character(len=LINELENGTH) :: fmtlstbn
607  !
608  ! -- Determine sizes
609  ldim = size(this%rlist, 1)
610  naux = size(this%auxvar, 1)
611  !
612  ! -- Dimension table
613  ntabrows = this%nlist
614  !
615  ! -- Start building format statement to parse this%label, which
616  ! contains the column headers (except for boundname and auxnames)
617  ipos = index(this%label, 'NO.')
618  if (ipos /= 0) then
619  write (cpos, '(i10)') ipos + 3
620  fmtlstbn = '(a'//trim(adjustl(cpos))
621  else
622  fmtlstbn = '(a7'
623  end if
624  ! -- Sequence number, layer, row, and column.
625  if (size(this%mshape) == 3) then
626  ntabcols = 4
627  fmtlstbn = trim(fmtlstbn)//',a7,a7,a7'
628  !
629  ! -- Sequence number, layer, and cell2d.
630  else if (size(this%mshape) == 2) then
631  ntabcols = 3
632  fmtlstbn = trim(fmtlstbn)//',a7,a7'
633  !
634  ! -- Sequence number and node.
635  else
636  ntabcols = 2
637  fmtlstbn = trim(fmtlstbn)//',a7'
638  end if
639  !
640  ! -- Add fields for non-optional real values
641  ntabcols = ntabcols + ldim
642  do i = 1, ldim
643  fmtlstbn = trim(fmtlstbn)//',a16'
644  end do
645  !
646  ! -- Add field for boundary name
647  if (this%inamedbound == 1) then
648  ntabcols = ntabcols + 1
649  fmtlstbn = trim(fmtlstbn)//',a16'
650  end if
651  !
652  ! -- Add fields for auxiliary variables
653  ntabcols = ntabcols + naux
654  do i = 1, naux
655  fmtlstbn = trim(fmtlstbn)//',a16'
656  end do
657  fmtlstbn = trim(fmtlstbn)//')'
658  !
659  ! -- Allocate words
660  allocate (words(ntabcols))
661  !
662  ! -- Parse this%label into words
663  read (this%label, fmtlstbn) (words(i), i=1, ntabcols)
664  !
665  ! -- Initialize the input table object
666  call table_cr(inputtab, ' ', ' ')
667  call inputtab%table_df(ntabrows, ntabcols, this%iout)
668  !
669  ! -- Add the columns
670  ipos = 1
671  call inputtab%initialize_column(words(ipos), 10, alignment=tabcenter)
672  !
673  ! -- Discretization
674  do i = 1, size(this%mshape)
675  ipos = ipos + 1
676  call inputtab%initialize_column(words(ipos), 7, alignment=tabcenter)
677  end do
678  !
679  ! -- Non-optional variables
680  do i = 1, ldim
681  ipos = ipos + 1
682  call inputtab%initialize_column(words(ipos), 16, alignment=tabcenter)
683  end do
684  !
685  ! -- Boundname
686  if (this%inamedbound == 1) then
687  ipos = ipos + 1
688  tag = 'BOUNDNAME'
689  call inputtab%initialize_column(tag, lenboundname, alignment=tableft)
690  end if
691  !
692  ! -- Aux variables
693  do i = 1, naux
694  call inputtab%initialize_column(this%auxname(i), 16, alignment=tabcenter)
695  end do
696  !
697  ! -- Write the table
698  do ii = 1, this%nlist
699  call inputtab%add_term(ii)
700  !
701  ! -- Discretization
702  if (size(this%mshape) == 3) then
703  nod = this%nodelist(ii)
704  call get_ijk(nod, this%mshape(2), this%mshape(3), this%mshape(1), &
705  i, j, k)
706  call inputtab%add_term(k)
707  call inputtab%add_term(i)
708  call inputtab%add_term(j)
709  else if (size(this%mshape) == 2) then
710  nod = this%nodelist(ii)
711  call get_ijk(nod, 1, this%mshape(2), this%mshape(1), i, j, k)
712  call inputtab%add_term(k)
713  call inputtab%add_term(j)
714  else
715  nod = this%nodelist(ii)
716  call inputtab%add_term(nod)
717  end if
718  !
719  ! -- Non-optional variables
720  do jj = 1, ldim
721  call inputtab%add_term(this%rlist(jj, ii))
722  end do
723  !
724  ! -- Boundname
725  if (this%inamedbound == 1) then
726  call inputtab%add_term(this%boundname(ii))
727  end if
728  !
729  ! -- Aux variables
730  do jj = 1, naux
731  call inputtab%add_term(this%auxvar(jj, ii))
732  end do
733  end do
734  !
735  ! -- Deallocate the local variables
736  call inputtab%table_da()
737  deallocate (inputtab)
738  nullify (inputtab)
739  deallocate (words)
@ tabcenter
centered table column
Definition: Constants.f90:172
@ tableft
left justified table column
Definition: Constants.f90:171
subroutine, public ulstlb(iout, label, caux, ncaux, naux)
Print a label for a list.
subroutine, public table_cr(this, name, title)
Definition: Table.f90:87
Here is the call graph for this function: