MOM6
MOM_file_parser.F90
1 !> The MOM6 facility to parse input files for runtime parameters
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 use mom_coms, only : root_pe, broadcast
7 use mom_error_handler, only : mom_error, fatal, warning, mom_mesg
8 use mom_error_handler, only : is_root_pe, stdlog, stdout
9 use mom_time_manager, only : get_time, time_type, get_ticks_per_second
10 use mom_time_manager, only : set_date, get_date, real_to_time, operator(-), set_time
11 use mom_document, only : doc_param, doc_module, doc_init, doc_end, doc_type
12 use mom_document, only : doc_openblock, doc_closeblock
13 use mom_string_functions, only : left_int, left_ints, slasher
14 use mom_string_functions, only : left_real, left_reals
15 
16 implicit none ; private
17 
18 integer, parameter, public :: max_param_files = 5 !< Maximum number of parameter files.
19 integer, parameter :: input_str_length = 320 !< Maximum line length in parameter file.
20 integer, parameter :: filename_length = 200 !< Maximum number of characters in file names.
21 
22 ! The all_PEs_read option should be eliminated with post-riga shared code.
23 logical :: all_pes_read = .false. !< If true, all PEs read the input files
24  !! TODO: Eliminate this parameter
25 
26 !>@{ Default values for parameters
27 logical, parameter :: report_unused_default = .false.
28 logical, parameter :: unused_params_fatal_default = .false.
29 logical, parameter :: log_to_stdout_default = .false.
30 logical, parameter :: complete_doc_default = .true.
31 logical, parameter :: minimal_doc_default = .true.
32 !!@}
33 
34 !> The valid lines extracted from an input parameter file without comments
35 type, private :: file_data_type ; private
36  integer :: num_lines = 0 !< The number of lines in this type
37  character(len=INPUT_STR_LENGTH), pointer, dimension(:) :: line => null() !< The line content
38  logical, pointer, dimension(:) :: line_used => null() !< If true, the line has been read
39 end type file_data_type
40 
41 !> A link in the list of variables that have already had override warnings issued
42 type :: link_parameter ; private
43  type(link_parameter), pointer :: next => null() !< Facilitates linked list
44  character(len=80) :: name !< Parameter name
45  logical :: hasissuedoverridewarning = .false. !< Has a default value
46 end type link_parameter
47 
48 !> Specify the active parameter block
49 type :: parameter_block ; private
50  character(len=240) :: name = '' !< The active parameter block name
51 end type parameter_block
52 
53 !> A structure that can be parsed to read and document run-time parameters.
54 type, public :: param_file_type ; private
55  integer :: nfiles = 0 !< The number of open files.
56  integer :: iounit(max_param_files) !< The unit numbers of open files.
57  character(len=FILENAME_LENGTH) :: filename(max_param_files) !< The names of the open files.
58  logical :: netcdf_file(max_param_files) !< If true, the input file is in NetCDF.
59  ! This is not yet implemented.
60  type(file_data_type) :: param_data(max_param_files) !< Structures that contain
61  !! the valid data lines from the parameter
62  !! files, enabling all subsequent reads of
63  !! parameter data to occur internally.
64  logical :: report_unused = report_unused_default !< If true, report any
65  !! parameter lines that are not used in the run.
66  logical :: unused_params_fatal = unused_params_fatal_default !< If true, kill
67  !! the run if there are any unused parameters.
68  logical :: log_to_stdout = log_to_stdout_default !< If true, all log
69  !! messages are also sent to stdout.
70  logical :: log_open = .false. !< True if the log file has been opened.
71  integer :: stdout !< The unit number from stdout().
72  integer :: stdlog !< The unit number from stdlog().
73  character(len=240) :: doc_file !< A file where all run-time parameters, their
74  !! settings and defaults are documented.
75  logical :: complete_doc = complete_doc_default !< If true, document all
76  !! run-time parameters.
77  logical :: minimal_doc = minimal_doc_default !< If true, document only those
78  !! run-time parameters that differ from defaults.
79  type(doc_type), pointer :: doc => null() !< A structure that contains information
80  !! related to parameter documentation.
81  type(link_parameter), pointer :: chain => null() !< Facilitates linked list
82  type(parameter_block), pointer :: blockname => null() !< Name of active parameter block
83 end type param_file_type
84 
85 public read_param, open_param_file, close_param_file, log_param, log_version
86 public doc_param, get_param
87 public clearparameterblock, openparameterblock, closeparameterblock
88 
89 !> An overloaded interface to read various types of parameters
90 interface read_param
91  module procedure read_param_int, read_param_real, read_param_logical, &
92  read_param_char, read_param_char_array, read_param_time, &
93  read_param_int_array, read_param_real_array
94 end interface
95 !> An overloaded interface to log the values of various types of parameters
96 interface log_param
97  module procedure log_param_int, log_param_real, log_param_logical, &
98  log_param_char, log_param_time, &
99  log_param_int_array, log_param_real_array
100 end interface
101 !> An overloaded interface to read and log the values of various types of parameters
102 interface get_param
103  module procedure get_param_int, get_param_real, get_param_logical, &
104  get_param_char, get_param_char_array, get_param_time, &
105  get_param_int_array, get_param_real_array
106 end interface
107 
108 !> An overloaded interface to log version information about modules
109 interface log_version
110  module procedure log_version_cs, log_version_plain
111 end interface
112 
113 contains
114 
115 !> Make the contents of a parameter input file availalble in a param_file_type
116 subroutine open_param_file(filename, CS, checkable, component, doc_file_dir)
117  character(len=*), intent(in) :: filename !< An input file name, optionally with the full path
118  type(param_file_type), intent(inout) :: cs !< The control structure for the file_parser module,
119  !! it is also a structure to parse for run-time parameters
120  logical, optional, intent(in) :: checkable !< If this is false, it disables checks of this
121  !! file for unused parameters. The default is True.
122  character(len=*), optional, intent(in) :: component !< If present, this component name is used
123  !! to generate parameter documentation file names; the default is"MOM"
124  character(len=*), optional, intent(in) :: doc_file_dir !< An optional directory in which to write out
125  !! the documentation files. The default is effectively './'.
126 
127  ! Local variables
128  logical :: file_exists, unit_in_use, netcdf_file, may_check
129  integer :: ios, iounit, strlen, i
130  character(len=240) :: doc_path
131  type(parameter_block), pointer :: block => null()
132 
133  may_check = .true. ; if (present(checkable)) may_check = checkable
134 
135  ! Check for non-blank filename
136  strlen = len_trim(filename)
137  if (strlen == 0) then
138  call mom_error(fatal, "open_param_file: Input file has not been specified.")
139  endif
140 
141  ! Check that this file has not already been opened
142  if (cs%nfiles > 0) then
143  inquire(file=trim(filename), number=iounit)
144  if (iounit /= -1) then
145  do i = 1, cs%nfiles
146  if (cs%iounit(i) == iounit) then
147  if (trim(cs%filename(1)) /= trim(filename)) then
148  call mom_error(fatal, &
149  "open_param_file: internal inconsistency! "//trim(filename)// &
150  " is registered as open but has the wrong unit number!")
151  else
152  call mom_error(warning, &
153  "open_param_file: file "//trim(filename)// &
154  " has already been opened. This should NOT happen!"// &
155  " Did you specify the same file twice in a namelist?")
156  return
157  endif ! filenames
158  endif ! unit numbers
159  enddo ! i
160  endif
161  endif
162 
163  ! Check that the file exists to readstdlog
164  inquire(file=trim(filename), exist=file_exists)
165  if (.not.file_exists) call mom_error(fatal, &
166  "open_param_file: Input file "// trim(filename)//" does not exist.")
167 
168  netcdf_file = .false.
169  if (strlen > 3) then
170  if (filename(strlen-2:strlen) == ".nc") netcdf_file = .true.
171  endif
172 
173  if (netcdf_file) &
174  call mom_error(fatal,"open_param_file: NetCDF files are not yet supported.")
175 
176  if (all_pes_read .or. is_root_pe()) then
177  ! Find an unused unit number.
178  do iounit=10,512
179  INQUIRE(iounit,opened=unit_in_use) ; if (.not.unit_in_use) exit
180  enddo
181  if (iounit >= 512) call mom_error(fatal, &
182  "open_param_file: No unused file unit could be found.")
183 
184  ! Open the parameter file.
185  open(iounit, file=trim(filename), access='SEQUENTIAL', &
186  form='FORMATTED', action='READ', position='REWIND', iostat=ios)
187  if (ios /= 0) call mom_error(fatal, "open_param_file: Error opening "// &
188  trim(filename))
189  else
190  iounit = 1
191  endif
192 
193  ! Store/register the unit and details
194  i = cs%nfiles + 1
195  cs%nfiles = i
196  cs%iounit(i) = iounit
197  cs%filename(i) = filename
198  cs%NetCDF_file(i) = netcdf_file
199  allocate(block) ; block%name = '' ; cs%blockName => block
200 
201  call mom_mesg("open_param_file: "// trim(filename)// &
202  " has been opened successfully.", 5)
203 
204  call populate_param_data(iounit, filename, cs%param_data(i))
205 
206  call read_param(cs,"SEND_LOG_TO_STDOUT",cs%log_to_stdout)
207  call read_param(cs,"REPORT_UNUSED_PARAMS",cs%report_unused)
208  call read_param(cs,"FATAL_UNUSED_PARAMS",cs%unused_params_fatal)
209  cs%doc_file = "MOM_parameter_doc"
210  if (present(component)) cs%doc_file = trim(component)//"_parameter_doc"
211  call read_param(cs,"DOCUMENT_FILE", cs%doc_file)
212  if (.not.may_check) then
213  cs%report_unused = .false.
214  cs%unused_params_fatal = .false.
215  endif
216 
217  ! Open the log file.
218  cs%stdlog = stdlog() ; cs%stdout = stdout()
219  cs%log_open = (stdlog() > 0)
220 
221  doc_path = cs%doc_file
222  if (len_trim(cs%doc_file) > 0) then
223  cs%complete_doc = complete_doc_default
224  call read_param(cs, "COMPLETE_DOCUMENTATION", cs%complete_doc)
225  cs%minimal_doc = minimal_doc_default
226  call read_param(cs, "MINIMAL_DOCUMENTATION", cs%minimal_doc)
227  if (present(doc_file_dir)) then ; if (len_trim(doc_file_dir) > 0) then
228  doc_path = trim(slasher(doc_file_dir))//trim(cs%doc_file)
229  endif ; endif
230  else
231  cs%complete_doc = .false.
232  cs%minimal_doc = .false.
233  endif
234  call doc_init(doc_path, cs%doc, minimal=cs%minimal_doc, complete=cs%complete_doc, &
235  layout=cs%complete_doc, debugging=cs%complete_doc)
236 
237 end subroutine open_param_file
238 
239 !> Close any open input files and deallocate memory associated with this param_file_type.
240 !! To use this type again, open_param_file would have to be called again.
241 subroutine close_param_file(CS, quiet_close, component)
242  type(param_file_type), intent(inout) :: cs !< The control structure for the file_parser module,
243  !! it is also a structure to parse for run-time parameters
244  logical, optional, intent(in) :: quiet_close !< if present and true, do not do any
245  !! logging with this call.
246  character(len=*), optional, intent(in) :: component !< If present, this component name is used
247  !! to generate parameter documentation file names
248  ! Local variables
249  character(len=128) :: docfile_default
250  character(len=40) :: mdl ! This module's name.
251  ! This include declares and sets the variable "version".
252 # include "version_variable.h"
253  integer :: i, n, num_unused
254 
255  if (present(quiet_close)) then ; if (quiet_close) then
256  do i = 1, cs%nfiles
257  if (all_pes_read .or. is_root_pe()) close(cs%iounit(i))
258  call mom_mesg("close_param_file: "// trim(cs%filename(i))// &
259  " has been closed successfully.", 5)
260  cs%iounit(i) = -1
261  cs%filename(i) = ''
262  cs%NetCDF_file(i) = .false.
263  deallocate (cs%param_data(i)%line)
264  deallocate (cs%param_data(i)%line_used)
265  enddo
266  cs%log_open = .false.
267  call doc_end(cs%doc)
268  return
269  endif ; endif
270 
271  ! Log the parameters for the parser.
272  mdl = "MOM_file_parser"
273  call log_version(cs, mdl, version, "")
274  call log_param(cs, mdl, "SEND_LOG_TO_STDOUT", cs%log_to_stdout, &
275  "If true, all log messages are also sent to stdout.", &
276  default=log_to_stdout_default)
277  call log_param(cs, mdl, "REPORT_UNUSED_PARAMS", cs%report_unused, &
278  "If true, report any parameter lines that are not used "//&
279  "in the run.", default=report_unused_default, &
280  debuggingparam=.true.)
281  call log_param(cs, mdl, "FATAL_UNUSED_PARAMS", cs%unused_params_fatal, &
282  "If true, kill the run if there are any unused "//&
283  "parameters.", default=unused_params_fatal_default, &
284  debuggingparam=.true.)
285  docfile_default = "MOM_parameter_doc"
286  if (present(component)) docfile_default = trim(component)//"_parameter_doc"
287  call log_param(cs, mdl, "DOCUMENT_FILE", cs%doc_file, &
288  "The basename for files where run-time parameters, their "//&
289  "settings, units and defaults are documented. Blank will "//&
290  "disable all parameter documentation.", default=docfile_default)
291  if (len_trim(cs%doc_file) > 0) then
292  call log_param(cs, mdl, "COMPLETE_DOCUMENTATION", cs%complete_doc, &
293  "If true, all run-time parameters are "//&
294  "documented in "//trim(cs%doc_file)//&
295  ".all .", default=complete_doc_default)
296  call log_param(cs, mdl, "MINIMAL_DOCUMENTATION", cs%minimal_doc, &
297  "If true, non-default run-time parameters are "//&
298  "documented in "//trim(cs%doc_file)//&
299  ".short .", default=minimal_doc_default)
300  endif
301 
302  num_unused = 0
303  do i = 1, cs%nfiles
304  if (is_root_pe() .and. (cs%report_unused .or. &
305  cs%unused_params_fatal)) then
306  ! Check for unused lines.
307  do n=1,cs%param_data(i)%num_lines
308  if (.not.cs%param_data(i)%line_used(n)) then
309  num_unused = num_unused + 1
310  if (cs%report_unused) &
311  call mom_error(warning, "Unused line in "//trim(cs%filename(i))// &
312  " : "//trim(cs%param_data(i)%line(n)))
313  endif
314  enddo
315  endif
316 
317  if (all_pes_read .or. is_root_pe()) close(cs%iounit(i))
318  call mom_mesg("close_param_file: "// trim(cs%filename(i))// &
319  " has been closed successfully.", 5)
320  cs%iounit(i) = -1
321  cs%filename(i) = ''
322  cs%NetCDF_file(i) = .false.
323  deallocate (cs%param_data(i)%line)
324  deallocate (cs%param_data(i)%line_used)
325  enddo
326 
327  if (is_root_pe() .and. (num_unused>0) .and. cs%unused_params_fatal) &
328  call mom_error(fatal, "Run stopped because of unused parameter lines.")
329 
330  cs%log_open = .false.
331  call doc_end(cs%doc)
332 
333 end subroutine close_param_file
334 
335 !> Read the contents of a parameter input file, and store the contents in a
336 !! file_data_type after removing comments and simplifying white space
337 subroutine populate_param_data(iounit, filename, param_data)
338  integer, intent(in) :: iounit !< The IO unit number that is open for filename
339  character(len=*), intent(in) :: filename !< An input file name, optionally with the full path
340  type(file_data_type), intent(inout) :: param_data !< A list of the input lines that set parameters
341  !! after comments have been stripped out.
342 
343  ! Local variables
344  character(len=INPUT_STR_LENGTH) :: line
345  integer :: num_lines
346  logical :: inMultiLineComment
347 
348  ! Find the number of keyword lines in a parameter file
349  ! Allocate the space to hold the lines in param_data%line
350  ! Populate param_data%line with the keyword lines from parameter file
351 
352  if (iounit <= 0) return
353 
354  if (all_pes_read .or. is_root_pe()) then
355  ! rewind the parameter file
356  rewind(iounit)
357 
358  ! count the number of valid entries in the parameter file
359  num_lines = 0
360  inmultilinecomment = .false.
361  do while(.true.)
362  read(iounit, '(a)', end=8, err=9) line
363  line = replacetabs(line)
364  if (inmultilinecomment) then
365  if (closemultilinecomment(line)) inmultilinecomment=.false.
366  else
367  if (lastnoncommentnonblank(line)>0) num_lines = num_lines + 1
368  if (openmultilinecomment(line)) inmultilinecomment=.true.
369  endif
370  enddo ! while (.true.)
371  8 continue ! get here when read() reaches EOF
372 
373  if (inmultilinecomment .and. is_root_pe()) &
374  call mom_error(fatal, 'MOM_file_parser : A C-style multi-line comment '// &
375  '(/* ... */) was not closed before the end of '//trim(filename))
376 
377  ! allocate space to hold contents of the parameter file
378  param_data%num_lines = num_lines
379  endif ! (is_root_pe())
380 
381  ! Broadcast the number of valid entries in parameter file
382  if (.not. all_pes_read) then
383  call broadcast(param_data%num_lines, root_pe())
384  endif
385 
386  ! Set up the space for storing the actual lines.
387  num_lines = param_data%num_lines
388  allocate (param_data%line(num_lines))
389  allocate (param_data%line_used(num_lines))
390  param_data%line(:) = ' '
391  param_data%line_used(:) = .false.
392 
393  ! Read the actual lines.
394  if (all_pes_read .or. is_root_pe()) then
395  ! rewind the parameter file
396  rewind(iounit)
397 
398  ! Populate param_data%line
399  num_lines = 0
400  do while(.true.)
401  read(iounit, '(a)', end=18, err=9) line
402  line = replacetabs(line)
403  if (inmultilinecomment) then
404  if (closemultilinecomment(line)) inmultilinecomment=.false.
405  else
406  if (lastnoncommentnonblank(line)>0) then
407  line = removecomments(line)
408  line = simplifywhitespace(line(:len_trim(line)))
409  num_lines = num_lines + 1
410  param_data%line(num_lines) = line
411  endif
412  if (openmultilinecomment(line)) inmultilinecomment=.true.
413  endif
414  enddo ! while (.true.)
415 18 continue ! get here when read() reaches EOF
416 
417  if (num_lines /= param_data%num_lines) &
418  call mom_error(fatal, 'MOM_file_parser : Found different number of '// &
419  'valid lines on second reading of '//trim(filename))
420  endif ! (is_root_pe())
421 
422  ! Broadcast the populated array param_data%line
423  if (.not. all_pes_read) then
424  call broadcast(param_data%line, input_str_length, root_pe())
425  endif
426 
427  return
428 
429 9 call mom_error(fatal, "MOM_file_parser : "//&
430  "Error while reading file "//trim(filename))
431 
432 end subroutine populate_param_data
433 
434 
435 !> Return True if a /* appears on this line without a closing */
436 function openmultilinecomment(string)
437  character(len=*), intent(in) :: string !< The input string to process
438  logical :: openmultilinecomment
439 
440  ! Local variables
441  integer :: icom, last
442 
443  openmultilinecomment = .false.
444  last = lastnoncommentindex(string)+1
445  icom = index(string(last:), "/*")
446  if (icom > 0) then
447  openmultilinecomment=.true.
448  last = last+icom+1
449  endif
450  icom = index(string(last:), "*/") ; if (icom > 0) openmultilinecomment=.false.
451 end function openmultilinecomment
452 
453 !> Return True if a */ appears on this line
454 function closemultilinecomment(string)
455  character(len=*), intent(in) :: string !< The input string to process
456  logical :: closemultilinecomment
457 ! True if a */ appears on this line
458  closemultilinecomment = .false.
459  if (index(string, "*/")>0) closemultilinecomment=.true.
460 end function closemultilinecomment
461 
462 !> Find position of last character before any comments, As marked by "!", "//", or "/*"
463 !! following F90, C++, or C syntax
464 function lastnoncommentindex(string)
465  character(len=*), intent(in) :: string !< The input string to process
466  integer :: lastnoncommentindex
467 
468  ! Local variables
469  integer :: icom, last
470 
471  ! This subroutine is the only place where a comment needs to be defined
472  last = len_trim(string)
473  icom = index(string(:last), "!") ; if (icom > 0) last = icom-1 ! F90 style
474  icom = index(string(:last), "//") ; if (icom > 0) last = icom-1 ! C++ style
475  icom = index(string(:last), "/*") ; if (icom > 0) last = icom-1 ! C style
476  lastnoncommentindex = last
477 end function lastnoncommentindex
478 
479 !> Find position of last non-blank character before any comments
480 function lastnoncommentnonblank(string)
481  character(len=*), intent(in) :: string !< The input string to process
482  integer :: lastnoncommentnonblank
483 
484  lastnoncommentnonblank = len_trim(string(:lastnoncommentindex(string))) ! Ignore remaining trailing blanks
485 end function lastnoncommentnonblank
486 
487 !> Returns a string with tabs replaced by a blank
488 function replacetabs(string)
489  character(len=*), intent(in) :: string !< The input string to process
490  character(len=len(string)) :: replacetabs
491 
492  integer :: i
493 
494  do i=1, len(string)
495  if (string(i:i)==achar(9)) then
496  replacetabs(i:i)=" "
497  else
498  replacetabs(i:i)=string(i:i)
499  endif
500  enddo
501 end function replacetabs
502 
503 !> Trims comments and leading blanks from string
504 function removecomments(string)
505  character(len=*), intent(in) :: string !< The input string to process
506  character(len=len(string)) :: removecomments
507 
508  integer :: last
509 
510  removecomments=repeat(" ",len(string))
511  last = lastnoncommentnonblank(string)
512  removecomments(:last)=adjustl(string(:last)) ! Copy only the non-comment part of string
513 end function removecomments
514 
515 !> Constructs a string with all repeated whitespace replaced with single blanks
516 !! and insert white space where it helps delineate tokens (e.g. around =)
517 function simplifywhitespace(string)
518  character(len=*), intent(in) :: string !< A string to modify to simpify white space
519  character(len=len(string)+16) :: simplifywhitespace
520 
521  ! Local variables
522  integer :: i,j
523  logical :: nonblank = .false., insidestring = .false.
524  character(len=1) :: quotechar=" "
525 
526  nonblank = .false.; insidestring = .false. ! NOTE: For some reason this line is needed??
527  i=0
528  simplifywhitespace=repeat(" ",len(string)+16)
529  do j=1,len_trim(string)
530  if (insidestring) then ! Do not change formatting inside strings
531  i=i+1
532  simplifywhitespace(i:i)=string(j:j)
533  if (string(j:j)==quotechar) insidestring=.false. ! End of string
534  else ! The following is outside of string delimiters
535  if (string(j:j)==" " .or. string(j:j)==achar(9)) then ! Space or tab
536  if (nonblank) then ! Only copy a blank if the preceeding character was non-blank
537  i=i+1
538  simplifywhitespace(i:i)=" " ! Not string(j:j) so that tabs are replace by blanks
539  nonblank=.false.
540  endif
541  elseif (string(j:j)=='"' .or. string(j:j)=="'") then ! Start a sting
542  i=i+1
543  simplifywhitespace(i:i)=string(j:j)
544  insidestring=.true.
545  quotechar=string(j:j) ! Keep copy of starting quote
546  nonblank=.true. ! For exit from string
547  elseif (string(j:j)=='=') then
548  ! Insert spaces if this character is "=" so that line contains " = "
549  if (nonblank) then
550  i=i+1
551  simplifywhitespace(i:i)=" "
552  endif
553  i=i+2
554  simplifywhitespace(i-1:i)=string(j:j)//" "
555  nonblank=.false.
556  else ! All other characters
557  i=i+1
558  simplifywhitespace(i:i)=string(j:j)
559  nonblank=.true.
560  endif
561  endif ! if (insideString)
562  enddo ! j
563  if (insidestring) then ! A missing close quote should be flagged
564  if (is_root_pe()) call mom_error(fatal, &
565  "There is a mismatched quote in the parameter file line: "// &
566  trim(string))
567  endif
568 end function simplifywhitespace
569 
570 !> This subroutine reads the value of an integer model parameter from a parameter file.
571 subroutine read_param_int(CS, varname, value, fail_if_missing)
572  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
573  !! it is also a structure to parse for run-time parameters
574  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
575  integer, intent(inout) :: value !< The value of the parameter that may be
576  !! read from the parameter file
577  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
578  !! if this variable is not found in the parameter file
579  ! Local variables
580  character(len=INPUT_STR_LENGTH) :: value_string(1)
581  logical :: found, defined
582 
583  call get_variable_line(cs, varname, found, defined, value_string)
584  if (found .and. defined .and. (len_trim(value_string(1)) > 0)) then
585  read(value_string(1),*,err = 1001) value
586  else
587  if (present(fail_if_missing)) then ; if (fail_if_missing) then
588  if (.not.found) then
589  call mom_error(fatal,'read_param_int: Unable to find variable '//trim(varname)// &
590  ' in any input files.')
591  else
592  call mom_error(fatal,'read_param_int: Variable '//trim(varname)// &
593  ' found but not set in input files.')
594  endif
595  endif ; endif
596  endif
597  return
598  1001 call mom_error(fatal,'read_param_int: read error for integer variable '//trim(varname)// &
599  ' parsing "'//trim(value_string(1))//'"')
600 end subroutine read_param_int
601 
602 !> This subroutine reads the values of an array of integer model parameters from a parameter file.
603 subroutine read_param_int_array(CS, varname, value, fail_if_missing)
604  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
605  !! it is also a structure to parse for run-time parameters
606  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
607  integer, dimension(:), intent(inout) :: value !< The value of the parameter that may be
608  !! read from the parameter file
609  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
610  !! if this variable is not found in the parameter file
611  ! Local variables
612  character(len=INPUT_STR_LENGTH) :: value_string(1)
613  logical :: found, defined
614 
615  call get_variable_line(cs, varname, found, defined, value_string)
616  if (found .and. defined .and. (len_trim(value_string(1)) > 0)) then
617  read(value_string(1),*,end=991,err=1002) value
618  991 return
619  else
620  if (present(fail_if_missing)) then ; if (fail_if_missing) then
621  if (.not.found) then
622  call mom_error(fatal,'read_param_int_array: Unable to find variable '//trim(varname)// &
623  ' in any input files.')
624  else
625  call mom_error(fatal,'read_param_int_array: Variable '//trim(varname)// &
626  ' found but not set in input files.')
627  endif
628  endif ; endif
629  endif
630  return
631  1002 call mom_error(fatal,'read_param_int_array: read error for integer array '//trim(varname)// &
632  ' parsing "'//trim(value_string(1))//'"')
633 end subroutine read_param_int_array
634 
635 !> This subroutine reads the value of a real model parameter from a parameter file.
636 subroutine read_param_real(CS, varname, value, fail_if_missing, scale)
637  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
638  !! it is also a structure to parse for run-time parameters
639  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
640  real, intent(inout) :: value !< The value of the parameter that may be
641  !! read from the parameter file
642  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
643  !! if this variable is not found in the parameter file
644  real, optional, intent(in) :: scale !< A scaling factor that the parameter is multiplied
645  !! by before it is returned.
646 
647  ! Local variables
648  character(len=INPUT_STR_LENGTH) :: value_string(1)
649  logical :: found, defined
650 
651  call get_variable_line(cs, varname, found, defined, value_string)
652  if (found .and. defined .and. (len_trim(value_string(1)) > 0)) then
653  read(value_string(1),*,err=1003) value
654  if (present(scale)) value = scale*value
655  else
656  if (present(fail_if_missing)) then ; if (fail_if_missing) then
657  if (.not.found) then
658  call mom_error(fatal,'read_param_real: Unable to find variable '//trim(varname)// &
659  ' in any input files.')
660  else
661  call mom_error(fatal,'read_param_real: Variable '//trim(varname)// &
662  ' found but not set in input files.')
663  endif
664  endif ; endif
665  endif
666  return
667  1003 call mom_error(fatal,'read_param_real: read error for real variable '//trim(varname)// &
668  ' parsing "'//trim(value_string(1))//'"')
669 end subroutine read_param_real
670 
671 !> This subroutine reads the values of an array of real model parameters from a parameter file.
672 subroutine read_param_real_array(CS, varname, value, fail_if_missing, scale)
673  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
674  !! it is also a structure to parse for run-time parameters
675  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
676  real, dimension(:), intent(inout) :: value !< The value of the parameter that may be
677  !! read from the parameter file
678  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
679  !! if this variable is not found in the parameter file
680  real, optional, intent(in) :: scale !< A scaling factor that the parameter is multiplied
681  !! by before it is returned.
682 
683  ! Local variables
684  character(len=INPUT_STR_LENGTH) :: value_string(1)
685  logical :: found, defined
686 
687  call get_variable_line(cs, varname, found, defined, value_string)
688  if (found .and. defined .and. (len_trim(value_string(1)) > 0)) then
689  read(value_string(1),*,end=991,err=1004) value
690 991 continue
691  if (present(scale)) value(:) = scale*value(:)
692  return
693  else
694  if (present(fail_if_missing)) then ; if (fail_if_missing) then
695  if (.not.found) then
696  call mom_error(fatal,'read_param_real_array: Unable to find variable '//trim(varname)// &
697  ' in any input files.')
698  else
699  call mom_error(fatal,'read_param_real_array: Variable '//trim(varname)// &
700  ' found but not set in input files.')
701  endif
702  endif ; endif
703  endif
704  return
705  1004 call mom_error(fatal,'read_param_real_array: read error for real array '//trim(varname)// &
706  ' parsing "'//trim(value_string(1))//'"')
707 end subroutine read_param_real_array
708 
709 !> This subroutine reads the value of a character string model parameter from a parameter file.
710 subroutine read_param_char(CS, varname, value, fail_if_missing)
711  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
712  !! it is also a structure to parse for run-time parameters
713  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
714  character(len=*), intent(inout) :: value !< The value of the parameter that may be
715  !! read from the parameter file
716  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
717  !! if this variable is not found in the parameter file
718  ! Local variables
719  character(len=INPUT_STR_LENGTH) :: value_string(1)
720  logical :: found, defined
721 
722  call get_variable_line(cs, varname, found, defined, value_string)
723  if (found) then
724  value = trim(strip_quotes(value_string(1)))
725  elseif (present(fail_if_missing)) then ; if (fail_if_missing) then
726  call mom_error(fatal,'Unable to find variable '//trim(varname)// &
727  ' in any input files.')
728  endif ; endif
729 
730 end subroutine read_param_char
731 
732 !> This subroutine reads the values of an array of character string model parameters from a parameter file.
733 subroutine read_param_char_array(CS, varname, value, fail_if_missing)
734  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
735  !! it is also a structure to parse for run-time parameters
736  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
737  character(len=*), dimension(:), intent(inout) :: value !< The value of the parameter that may be
738  !! read from the parameter file
739  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
740  !! if this variable is not found in the parameter file
741 
742  ! Local variables
743  character(len=INPUT_STR_LENGTH) :: value_string(1), loc_string
744  logical :: found, defined
745  integer :: i, i_out
746 
747  call get_variable_line(cs, varname, found, defined, value_string)
748  if (found) then
749  loc_string = trim(value_string(1))
750  i = index(loc_string,",")
751  i_out = 1
752  do while(i>0)
753  value(i_out) = trim(strip_quotes(loc_string(:i-1)))
754  i_out = i_out+1
755  loc_string = trim(adjustl(loc_string(i+1:)))
756  i = index(loc_string,",")
757  enddo
758  if (len_trim(loc_string)>0) then
759  value(i_out) = trim(strip_quotes(adjustl(loc_string)))
760  i_out = i_out+1
761  endif
762  do i=i_out,SIZE(value) ; value(i) = " " ; enddo
763  elseif (present(fail_if_missing)) then ; if (fail_if_missing) then
764  call mom_error(fatal,'Unable to find variable '//trim(varname)// &
765  ' in any input files.')
766  endif ; endif
767 
768 end subroutine read_param_char_array
769 
770 !> This subroutine reads the value of a logical model parameter from a parameter file.
771 subroutine read_param_logical(CS, varname, value, fail_if_missing)
772  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
773  !! it is also a structure to parse for run-time parameters
774  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
775  logical, intent(inout) :: value !< The value of the parameter that may be
776  !! read from the parameter file
777  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
778  !! if this variable is not found in the parameter file
779 
780  ! Local variables
781  character(len=INPUT_STR_LENGTH) :: value_string(1)
782  logical :: found, defined
783 
784  call get_variable_line(cs, varname, found, defined, value_string, paramislogical=.true.)
785  if (found) then
786  value = defined
787  elseif (present(fail_if_missing)) then ; if (fail_if_missing) then
788  call mom_error(fatal,'Unable to find variable '//trim(varname)// &
789  ' in any input files.')
790  endif ; endif
791 end subroutine read_param_logical
792 
793 !> This subroutine reads the value of a time_type model parameter from a parameter file.
794 subroutine read_param_time(CS, varname, value, timeunit, fail_if_missing, date_format)
795  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
796  !! it is also a structure to parse for run-time parameters
797  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
798  type(time_type), intent(inout) :: value !< The value of the parameter that may be
799  !! read from the parameter file
800  real, optional, intent(in) :: timeunit !< The number of seconds in a time unit for real-number input.
801  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
802  !! if this variable is not found in the parameter file
803  logical, optional, intent(out) :: date_format !< If present, this indicates whether this
804  !! parameter was read in a date format, so that it can
805  !! later be logged in the same format.
806 
807  ! Local variables
808  character(len=INPUT_STR_LENGTH) :: value_string(1)
809  character(len=240) :: err_msg
810  logical :: found, defined
811  real :: real_time, time_unit
812  integer :: vals(7)
813 
814  if (present(date_format)) date_format = .false.
815 
816  call get_variable_line(cs, varname, found, defined, value_string)
817  if (found .and. defined .and. (len_trim(value_string(1)) > 0)) then
818  ! Determine whether value string should be parsed for a real number
819  ! or a date, in either a string format or a comma-delimited list of values.
820  if ((index(value_string(1),'-') > 0) .and. &
821  (index(value_string(1),'-',back=.true.) > index(value_string(1),'-'))) then
822  ! There are two dashes, so this must be a date format.
823  value = set_date(value_string(1), err_msg=err_msg)
824  if (len_trim(err_msg) > 0) call mom_error(fatal,'read_param_time: '//&
825  trim(err_msg)//' in integer list read error for time-type variable '//&
826  trim(varname)// ' parsing "'//trim(value_string(1))//'"')
827  if (present(date_format)) date_format = .true.
828  elseif (index(value_string(1),',') > 0) then
829  ! Initialize vals with an invalid date.
830  vals(:) = (/ -999, -999, -999, 0, 0, 0, 0 /)
831  read(value_string(1),*,end=995,err=1005) vals
832  995 continue
833  if ((vals(1) < 0) .or. (vals(2) < 0) .or. (vals(3) < 0)) &
834  call mom_error(fatal,'read_param_time: integer list read error for time-type variable '//&
835  trim(varname)// ' parsing "'//trim(value_string(1))//'"')
836  value = set_date(vals(1), vals(2), vals(3), vals(4), vals(5), vals(6), &
837  vals(7), err_msg=err_msg)
838  if (len_trim(err_msg) > 0) call mom_error(fatal,'read_param_time: '//&
839  trim(err_msg)//' in integer list read error for time-type variable '//&
840  trim(varname)// ' parsing "'//trim(value_string(1))//'"')
841  if (present(date_format)) date_format = .true.
842  else
843  time_unit = 1.0 ; if (present(timeunit)) time_unit = timeunit
844  read( value_string(1), *) real_time
845  value = real_to_time(real_time*time_unit)
846  endif
847  else
848  if (present(fail_if_missing)) then ; if (fail_if_missing) then
849  if (.not.found) then
850  call mom_error(fatal,'Unable to find variable '//trim(varname)// &
851  ' in any input files.')
852  else
853  call mom_error(fatal,'Variable '//trim(varname)// &
854  ' found but not set in input files.')
855  endif
856  endif ; endif
857  endif
858  return
859  1005 call mom_error(fatal,'read_param_time: read error for time-type variable '//&
860  trim(varname)// ' parsing "'//trim(value_string(1))//'"')
861 end subroutine read_param_time
862 
863 !> This function removes single and double quotes from a character string
864 function strip_quotes(val_str)
865  character(len=*) :: val_str !< The character string to work on
866  character(len=INPUT_STR_LENGTH) :: strip_quotes
867  ! Local variables
868  integer :: i
869  strip_quotes = val_str
870  i = index(strip_quotes,achar(34)) ! Double quote
871  do while (i>0)
872  if (i > 1) then ; strip_quotes = strip_quotes(:i-1)//strip_quotes(i+1:)
873  else ; strip_quotes = strip_quotes(2:) ; endif
874  i = index(strip_quotes,achar(34)) ! Double quote
875  enddo
876  i = index(strip_quotes,achar(39)) ! Single quote
877  do while (i>0)
878  if (i > 1) then ; strip_quotes = strip_quotes(:i-1)//strip_quotes(i+1:)
879  else ; strip_quotes = strip_quotes(2:) ; endif
880  i = index(strip_quotes,achar(39)) ! Single quote
881  enddo
882 end function strip_quotes
883 
884 !> This subtoutine extracts the contents of lines in the param_file_type that refer to
885 !! a named parameter. The value_string that is returned must be interepreted in a way
886 !! that depends on the type of this variable.
887 subroutine get_variable_line(CS, varname, found, defined, value_string, paramIsLogical)
888  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
889  !! it is also a structure to parse for run-time parameters
890  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
891  logical, intent(out) :: found !< If true, this parameter has been found in CS
892  logical, intent(out) :: defined !< If true, this parameter is set (or true) in the CS
893  character(len=*), intent(out) :: value_string(:) !< A string that encodes the new value
894  logical, optional, intent(in) :: paramIsLogical !< If true, this is a logical parameter
895  !! that can be simply defined without parsing a value_string.
896 
897  ! Local variables
898  character(len=INPUT_STR_LENGTH) :: val_str, lname, origLine
899  character(len=INPUT_STR_LENGTH) :: line, continuationBuffer, blockName
900  character(len=FILENAME_LENGTH) :: filename
901  integer :: is, id, isd, isu, ise, iso, verbose, ipf
902  integer :: last, last1, ival, oval, max_vals, count, contBufSize
903  character(len=52) :: set
904  logical :: found_override, found_equals
905  logical :: found_define, found_undef
906  logical :: force_cycle, defined_in_line, continuedLine
907  logical :: variableKindIsLogical, valueIsSame
908  logical :: inWrongBlock, fullPathParameter
909  logical, parameter :: requireNamedClose = .false.
910  set = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"
911  continuationbuffer = repeat(" ",input_str_length)
912  contbufsize = 0
913  verbose = 1
914 
915  variablekindislogical=.false.
916  if (present(paramislogical)) variablekindislogical = paramislogical
917 
918  ! Find the first instance (if any) where the named variable is found, and
919  ! return variables indicating whether this variable is defined and the string
920  ! that contains the value of this variable.
921  found = .false.
922  oval = 0; ival = 0
923  max_vals = SIZE(value_string)
924  do is=1,max_vals ; value_string(is) = " " ; enddo
925 
926  paramfile_loop: do ipf = 1, cs%nfiles
927  filename = cs%filename(ipf)
928  continuedline = .false.
929  blockname = ''
930 
931  ! Scan through each line of the file
932  do count = 1, cs%param_data(ipf)%num_lines
933  line = cs%param_data(ipf)%line(count)
934  last = len_trim(line)
935 
936  last1 = max(1,last)
937  ! Check if line ends in continuation character (either & or \)
938  ! Note achar(92) is a backslash
939  if (line(last1:last1) == achar(92).or.line(last1:last1) == "&") then
940  continuationbuffer(contbufsize+1:contbufsize+len_trim(line))=line(:last-1)
941  contbufsize=contbufsize + len_trim(line)-1
942  continuedline = .true.
943  if (count==cs%param_data(ipf)%num_lines .and. is_root_pe()) &
944  call mom_error(fatal, "MOM_file_parser : the last line"// &
945  " of the file ends in a continuation character but"// &
946  " there are no more lines to read. "// &
947  " Line: '"//trim(line(:last))//"'"//&
948  " in file "//trim(filename)//".")
949  cycle ! cycle inorder to append the next line of the file
950  elseif (continuedline) then
951  ! If we reached this point then this is the end of line continuation
952  continuationbuffer(contbufsize+1:contbufsize+len_trim(line))=line(:last)
953  line = continuationbuffer
954  continuationbuffer=repeat(" ",input_str_length) ! Clear for next use
955  contbufsize = 0
956  continuedline = .false.
957  last = len_trim(line)
958  endif
959 
960  origline = trim(line) ! Keep original for error messages
961 
962  ! Check for '#override' at start of line
963  found_override = .false.; found_define = .false.; found_undef = .false.
964  iso = index(line(:last), "#override " )!; if (is > 0) found_override = .true.
965  if (iso>1) call mom_error(fatal, "MOM_file_parser : #override was found "// &
966  " but was not the first keyword."// &
967  " Line: '"//trim(line(:last))//"'"//&
968  " in file "//trim(filename)//".")
969  if (iso==1) then
970  found_override = .true.
971  if (index(line(:last), "#override define ")==1) found_define = .true.
972  if (index(line(:last), "#override undef ")==1) found_undef = .true.
973  line = trim(adjustl(line(iso+10:last))); last = len_trim(line)
974  endif
975 
976  ! Check for start of fortran namelist, ie. '&namelist'
977  if (index(line(:last),'&')==1) then
978  iso=index(line(:last),' ')
979  if (iso>0) then ! possibly simething else on this line
980  blockname = pushblocklevel(blockname,line(2:iso-1))
981  line=trim(adjustl(line(iso:last)))
982  last=len_trim(line)
983  if (last==0) cycle ! nothing else on this line
984  else ! just the namelist on this line
985  if (len_trim(blockname)>0) then
986  blockname = trim(blockname) // '%' //trim(line(2:last))
987  else
988  blockname = trim(line(2:last))
989  endif
990  call flag_line_as_read(cs%param_data(ipf)%line_used,count)
991  cycle
992  endif
993  endif
994 
995  ! Newer form of parameter block, block%, %block or block%param or
996  iso=index(line(:last),'%')
997  fullpathparameter = .false.
998  if (iso==1) then ! % is first character means this is a close
999  if (len_trim(blockname)==0 .and. is_root_pe()) call mom_error(fatal, &
1000  'get_variable_line: An extra close block was encountered. Line="'// &
1001  trim(line(:last))//'"' )
1002  if (last>1 .and. trim(blockname)/=trim(line(2:last)) .and. is_root_pe()) &
1003  call mom_error(fatal, 'get_variable_line: A named close for a parameter'// &
1004  ' block did not match the open block. Line="'//trim(line(:last))//'"' )
1005  if (last==1 .and. requirenamedclose) & ! line = '%' is a generic (unnamed) close
1006  call mom_error(fatal, 'get_variable_line: A named close for a parameter'// &
1007  ' block is required but found "%". Block="'//trim(blockname)//'"' )
1008  blockname = popblocklevel(blockname)
1009  call flag_line_as_read(cs%param_data(ipf)%line_used,count)
1010  elseif (iso==last) then ! This is a new block if % is last character
1011  blockname = pushblocklevel(blockname, line(:iso-1))
1012  call flag_line_as_read(cs%param_data(ipf)%line_used,count)
1013  else ! This is of the form block%parameter = ... (full path parameter)
1014  iso=index(line(:last),'%',.true.)
1015  ! Check that the parameter block names on the line matches the state set by the caller
1016  if (iso>0 .and. trim(cs%blockName%name)==trim(line(:iso-1))) then
1017  fullpathparameter = .true.
1018  line = trim(line(iso+1:last)) ! Strip away the block name for subsequent processing
1019  last = len_trim(line)
1020  endif
1021  endif
1022 
1023  ! We should only interpret this line if this block is the active block
1024  inwrongblock = .false.
1025  if (len_trim(blockname)>0) then ! In a namelist block in file
1026  if (trim(cs%blockName%name)/=trim(blockname)) inwrongblock = .true. ! Not in the required block
1027  endif
1028  if (len_trim(cs%blockName%name)>0) then ! In a namelist block in the model
1029  if (trim(cs%blockName%name)/=trim(blockname)) inwrongblock = .true. ! Not in the required block
1030  endif
1031 
1032  ! Check for termination of a fortran namelist (with a '/')
1033  if (line(last:last)=='/') then
1034  if (len_trim(blockname)==0 .and. is_root_pe()) call mom_error(fatal, &
1035  'get_variable_line: An extra namelist/block end was encountered. Line="'// &
1036  trim(line(:last))//'"' )
1037  blockname = popblocklevel(blockname)
1038  last = last - 1 ! Ignore the termination character from here on
1039  endif
1040  if (inwrongblock .and. .not. fullpathparameter) then
1041  if (index(" "//line(:last+1), " "//trim(varname)//" ")>0) &
1042  call mom_error(warning,"MOM_file_parser : "//trim(varname)// &
1043  ' found outside of block '//trim(cs%blockName%name)//'%. Ignoring.')
1044  cycle
1045  endif
1046 
1047  ! Determine whether this line mentions the named parameter or not
1048  if (index(" "//line(:last)//" ", " "//trim(varname)//" ") == 0) cycle
1049 
1050  ! Detect keywords
1051  found_equals = .false.
1052  isd = index(line(:last), "define" )!; if (isd > 0) found_define = .true.
1053  isu = index(line(:last), "undef" )!; if (isu > 0) found_undef = .true.
1054  ise = index(line(:last), " = " ); if (ise > 1) found_equals = .true.
1055  if (index(line(:last), "#define ")==1) found_define = .true.
1056  if (index(line(:last), "#undef ")==1) found_undef = .true.
1057 
1058  ! Check for missing, mutually exclusive or incomplete keywords
1059  if (is_root_pe()) then
1060  if (.not. (found_define .or. found_undef .or. found_equals)) &
1061  call mom_error(fatal, "MOM_file_parser : the parameter name '"// &
1062  trim(varname)//"' was found without define or undef."// &
1063  " Line: '"//trim(line(:last))//"'"//&
1064  " in file "//trim(filename)//".")
1065  if (found_define .and. found_undef) call mom_error(fatal, &
1066  "MOM_file_parser : Both 'undef' and 'define' occur."// &
1067  " Line: '"//trim(line(:last))//"'"//&
1068  " in file "//trim(filename)//".")
1069  if (found_equals .and. (found_define .or. found_undef)) &
1070  call mom_error(fatal, &
1071  "MOM_file_parser : Both 'a=b' and 'undef/define' syntax occur."// &
1072  " Line: '"//trim(line(:last))//"'"//&
1073  " in file "//trim(filename)//".")
1074  if (found_override .and. .not. (found_define .or. found_undef .or. found_equals)) &
1075  call mom_error(fatal, "MOM_file_parser : override was found "// &
1076  " without a define or undef."// &
1077  " Line: '"//trim(line(:last))//"'"//&
1078  " in file "//trim(filename)//".")
1079  endif
1080 
1081  ! Interpret the line and collect values, if any
1082  if (found_define) then
1083  ! Move starting pointer to first letter of defined name.
1084  is = isd + 5 + scan(line(isd+6:last), set)
1085 
1086  id = scan(line(is:last), ' ') ! Find space between name and value
1087  if ( id == 0 ) then
1088  ! There is no space so the name is simply being defined.
1089  lname = trim(line(is:last))
1090  if (trim(lname) /= trim(varname)) cycle
1091  val_str = " "
1092  else
1093  ! There is a string or number after the name.
1094  lname = trim(line(is:is+id-1))
1095  if (trim(lname) /= trim(varname)) cycle
1096  val_str = trim(adjustl(line(is+id:last)))
1097  endif
1098  found = .true. ; defined_in_line = .true.
1099  elseif (found_undef) then
1100  ! Move starting pointer to first letter of undefined name.
1101  is = isu + 4 + scan(line(isu+5:last), set)
1102 
1103  id = scan(line(is:last), ' ') ! Find the first space after the name.
1104  if (id > 0) last = is + id - 1
1105  lname = trim(line(is:last))
1106  if (trim(lname) /= trim(varname)) cycle
1107  val_str = " "
1108  found = .true. ; defined_in_line = .false.
1109  elseif (found_equals) then
1110  ! Move starting pointer to first letter of defined name.
1111  is = scan(line(1:ise), set)
1112  lname = trim(line(is:ise-1))
1113  if (trim(lname) /= trim(varname)) cycle
1114  val_str = trim(adjustl(line(ise+3:last)))
1115  if (variablekindislogical) then ! Special handling for logicals
1116  read(val_str(:len_trim(val_str)),*) defined_in_line
1117  else
1118  defined_in_line = .true.
1119  endif
1120  found = .true.
1121  else
1122  call mom_error(fatal, "MOM_file_parser (non-root PE?): the parameter name '"// &
1123  trim(varname)//"' was found without an assignment, define or undef."// &
1124  " Line: '"//trim(line(:last))//"'"//" in file "//trim(filename)//".")
1125  endif
1126 
1127  ! This line has now been used.
1128  call flag_line_as_read(cs%param_data(ipf)%line_used,count)
1129 
1130  ! Detect inconsistencies
1131  force_cycle = .false.
1132  valueissame = (trim(val_str) == trim(value_string(max_vals)))
1133  if (found_override .and. (oval >= max_vals)) then
1134  if (is_root_pe()) then
1135  if ((defined_in_line .neqv. defined) .or. .not. valueissame) then
1136  call mom_error(fatal,"MOM_file_parser : "//trim(varname)// &
1137  " found with multiple inconsistent overrides."// &
1138  " Line A: '"//trim(value_string(max_vals))//"'"//&
1139  " Line B: '"//trim(line(:last))//"'"//&
1140  " in file "//trim(filename)//" caused the model failure.")
1141  else
1142  call mom_error(warning,"MOM_file_parser : "//trim(varname)// &
1143  " over-ridden more times than is permitted."// &
1144  " Line: '"//trim(line(:last))//"'"//&
1145  " in file "//trim(filename)//" is being ignored.")
1146  endif
1147  endif
1148  force_cycle = .true.
1149  endif
1150  if (.not.found_override .and. (oval > 0)) then
1151  if (is_root_pe()) &
1152  call mom_error(warning,"MOM_file_parser : "//trim(varname)// &
1153  " has already been over-ridden."// &
1154  " Line: '"//trim(line(:last))//"'"//&
1155  " in file "//trim(filename)//" is being ignored.")
1156  force_cycle = .true.
1157  endif
1158  if (.not.found_override .and. (ival >= max_vals)) then
1159  if (is_root_pe()) then
1160  if ((defined_in_line .neqv. defined) .or. .not. valueissame) then
1161  call mom_error(fatal,"MOM_file_parser : "//trim(varname)// &
1162  " found with multiple inconsistent definitions."// &
1163  " Line A: '"//trim(value_string(max_vals))//"'"//&
1164  " Line B: '"//trim(line(:last))//"'"//&
1165  " in file "//trim(filename)//" caused the model failure.")
1166  else
1167  call mom_error(warning,"MOM_file_parser : "//trim(varname)// &
1168  " occurs more times than is permitted."// &
1169  " Line: '"//trim(line(:last))//"'"//&
1170  " in file "//trim(filename)//" is being ignored.")
1171  endif
1172  endif
1173  force_cycle = .true.
1174  endif
1175  if (force_cycle) cycle
1176 
1177  ! Store new values
1178  if (found_override) then
1179  oval = oval + 1
1180  value_string(oval) = trim(val_str)
1181  defined = defined_in_line
1182  if (verbose > 0 .and. ival > 0 .and. is_root_pe() .and. &
1183  .not. overridewarninghasbeenissued(cs%chain, trim(varname)) ) &
1184  call mom_error(warning,"MOM_file_parser : "//trim(varname)// &
1185  " over-ridden. Line: '"//trim(line(:last))//"'"//&
1186  " in file "//trim(filename)//".")
1187  else ! (.not. found_overide)
1188  ival = ival + 1
1189  value_string(ival) = trim(val_str)
1190  defined = defined_in_line
1191  if (verbose > 1 .and. is_root_pe()) &
1192  call mom_error(warning,"MOM_file_parser : "//trim(varname)// &
1193  " set. Line: '"//trim(line(:last))//"'"//&
1194  " in file "//trim(filename)//".")
1195  endif
1196 
1197  enddo ! CS%param_data(ipf)%num_lines
1198 
1199  if (len_trim(blockname)>0 .and. is_root_pe()) call mom_error(fatal, &
1200  'A namelist/parameter block was not closed. Last open block appears '// &
1201  'to be "'//trim(blockname)//'".')
1202 
1203  enddo paramfile_loop
1204 
1205 end subroutine get_variable_line
1206 
1207 !> Record that a line has been used to set a parameter
1208 subroutine flag_line_as_read(line_used, count)
1209  logical, dimension(:), pointer :: line_used !< A structure indicating which lines have been read
1210  integer, intent(in) :: count !< The parameter on this line number has been read
1211  line_used(count) = .true.
1212 end subroutine flag_line_as_read
1213 
1214 !> Returns true if an override warning has been issued for the variable varName
1215 function overridewarninghasbeenissued(chain, varName)
1216  type(link_parameter), pointer :: chain !< The linked list of variables that have already had
1217  !! override warnings issued
1218  character(len=*), intent(in) :: varname !< The name of the variable being queried for warnings
1219  logical :: overridewarninghasbeenissued
1220  ! Local variables
1221  type(link_parameter), pointer :: newlink => null(), this => null()
1222 
1223  overridewarninghasbeenissued = .false.
1224  this => chain
1225  do while( associated(this) )
1226  if (trim(varname) == trim(this%name)) then
1227  overridewarninghasbeenissued = .true.
1228  return
1229  endif
1230  this => this%next
1231  enddo
1232  allocate(newlink)
1233  newlink%name = trim(varname)
1234  newlink%hasIssuedOverrideWarning = .true.
1235  newlink%next => chain
1236  chain => newlink
1237 end function overridewarninghasbeenissued
1238 
1239 ! The following subroutines write out to a log file.
1240 
1241 !> Log the version of a module to a log file and/or stdout, and/or to the
1242 !! parameter documentation file.
1243 subroutine log_version_cs(CS, modulename, version, desc)
1244  type(param_file_type), intent(in) :: CS !< File parser type
1245  character(len=*), intent(in) :: modulename !< Name of calling module
1246  character(len=*), intent(in) :: version !< Version string of module
1247  character(len=*), optional, intent(in) :: desc !< Module description
1248  ! Local variables
1249  character(len=240) :: mesg
1250 
1251  mesg = trim(modulename)//": "//trim(version)
1252  if (is_root_pe()) then
1253  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1254  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1255  endif
1256 
1257  if (present(desc)) call doc_module(cs%doc, modulename, desc)
1258 
1259 end subroutine log_version_cs
1260 
1261 !> Log the version of a module to a log file and/or stdout.
1262 subroutine log_version_plain(modulename, version)
1263  character(len=*), intent(in) :: modulename !< Name of calling module
1264  character(len=*), intent(in) :: version !< Version string of module
1265  ! Local variables
1266  character(len=240) :: mesg
1267 
1268  mesg = trim(modulename)//": "//trim(version)
1269  if (is_root_pe()) then
1270  write(stdlog(),'(a)') trim(mesg)
1271  endif
1272 
1273 end subroutine log_version_plain
1274 
1275 !> Log the name and value of an integer model parameter in documentation files.
1276 subroutine log_param_int(CS, modulename, varname, value, desc, units, &
1277  default, layoutParam, debuggingParam)
1278  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1279  !! it is also a structure to parse for run-time parameters
1280  character(len=*), intent(in) :: modulename !< The name of the module using this parameter
1281  character(len=*), intent(in) :: varname !< The name of the parameter to log
1282  integer, intent(in) :: value !< The value of the parameter to log
1283  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1284  !! present, this parameter is not written to a doc file
1285  character(len=*), optional, intent(in) :: units !< The units of this parameter
1286  integer, optional, intent(in) :: default !< The default value of the parameter
1287  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1288  !! logged in the layout parameter file
1289  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1290  !! logged in the debugging parameter file
1291 
1292  character(len=240) :: mesg, myunits
1293 
1294  write(mesg, '(" ",a," ",a,": ",a)') trim(modulename), trim(varname), trim(left_int(value))
1295  if (is_root_pe()) then
1296  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1297  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1298  endif
1299 
1300  myunits=" "; if (present(units)) write(myunits(1:240),'(A)') trim(units)
1301  if (present(desc)) &
1302  call doc_param(cs%doc, varname, desc, myunits, value, default, &
1303  layoutparam=layoutparam, debuggingparam=debuggingparam)
1304 
1305 end subroutine log_param_int
1306 
1307 !> Log the name and values of an array of integer model parameter in documentation files.
1308 subroutine log_param_int_array(CS, modulename, varname, value, desc, &
1309  units, default, layoutParam, debuggingParam)
1310  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1311  !! it is also a structure to parse for run-time parameters
1312  character(len=*), intent(in) :: modulename !< The name of the module using this parameter
1313  character(len=*), intent(in) :: varname !< The name of the parameter to log
1314  integer, dimension(:), intent(in) :: value !< The value of the parameter to log
1315  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1316  !! present, this parameter is not written to a doc file
1317  character(len=*), optional, intent(in) :: units !< The units of this parameter
1318  integer, optional, intent(in) :: default !< The default value of the parameter
1319  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1320  !! logged in the layout parameter file
1321  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1322  !! logged in the debugging parameter file
1323 
1324  character(len=1320) :: mesg
1325  character(len=240) :: myunits
1326 
1327  write(mesg, '(" ",a," ",a,": ",A)') trim(modulename), trim(varname), trim(left_ints(value))
1328  if (is_root_pe()) then
1329  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1330  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1331  endif
1332 
1333  myunits=" "; if (present(units)) write(myunits(1:240),'(A)') trim(units)
1334  if (present(desc)) &
1335  call doc_param(cs%doc, varname, desc, myunits, value, default, &
1336  layoutparam=layoutparam, debuggingparam=debuggingparam)
1337 
1338 end subroutine log_param_int_array
1339 
1340 !> Log the name and value of a real model parameter in documentation files.
1341 subroutine log_param_real(CS, modulename, varname, value, desc, units, &
1342  default, debuggingParam)
1343  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1344  !! it is also a structure to parse for run-time parameters
1345  character(len=*), intent(in) :: modulename !< The name of the calling module
1346  character(len=*), intent(in) :: varname !< The name of the parameter to log
1347  real, intent(in) :: value !< The value of the parameter to log
1348  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1349  !! present, this parameter is not written to a doc file
1350  character(len=*), optional, intent(in) :: units !< The units of this parameter
1351  real, optional, intent(in) :: default !< The default value of the parameter
1352  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1353  !! logged in the debugging parameter file
1354 
1355  character(len=240) :: mesg, myunits
1356 
1357  write(mesg, '(" ",a," ",a,": ",a)') &
1358  trim(modulename), trim(varname), trim(left_real(value))
1359  if (is_root_pe()) then
1360  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1361  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1362  endif
1363 
1364  myunits="not defined"; if (present(units)) write(myunits(1:240),'(A)') trim(units)
1365  if (present(desc)) &
1366  call doc_param(cs%doc, varname, desc, myunits, value, default, &
1367  debuggingparam=debuggingparam)
1368 
1369 end subroutine log_param_real
1370 
1371 !> Log the name and values of an array of real model parameter in documentation files.
1372 subroutine log_param_real_array(CS, modulename, varname, value, desc, &
1373  units, default, debuggingParam)
1374  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1375  !! it is also a structure to parse for run-time parameters
1376  character(len=*), intent(in) :: modulename !< The name of the calling module
1377  character(len=*), intent(in) :: varname !< The name of the parameter to log
1378  real, dimension(:), intent(in) :: value !< The value of the parameter to log
1379  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1380  !! present, this parameter is not written to a doc file
1381  character(len=*), optional, intent(in) :: units !< The units of this parameter
1382  real, optional, intent(in) :: default !< The default value of the parameter
1383  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1384  !! logged in the debugging parameter file
1385 
1386  character(len=1320) :: mesg
1387  character(len=240) :: myunits
1388 
1389  !write(mesg, '(" ",a," ",a,": ",ES19.12,99(",",ES19.12))') &
1390  !write(mesg, '(" ",a," ",a,": ",G,99(",",G))') &
1391  ! trim(modulename), trim(varname), value
1392  write(mesg, '(" ",a," ",a,": ",a)') &
1393  trim(modulename), trim(varname), trim(left_reals(value))
1394  if (is_root_pe()) then
1395  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1396  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1397  endif
1398 
1399  myunits="not defined"; if (present(units)) write(myunits(1:240),'(A)') trim(units)
1400  if (present(desc)) &
1401  call doc_param(cs%doc, varname, desc, myunits, value, default, &
1402  debuggingparam=debuggingparam)
1403 
1404 end subroutine log_param_real_array
1405 
1406 !> Log the name and value of a logical model parameter in documentation files.
1407 subroutine log_param_logical(CS, modulename, varname, value, desc, &
1408  units, default, layoutParam, debuggingParam)
1409  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1410  !! it is also a structure to parse for run-time parameters
1411  character(len=*), intent(in) :: modulename !< The name of the calling module
1412  character(len=*), intent(in) :: varname !< The name of the parameter to log
1413  logical, intent(in) :: value !< The value of the parameter to log
1414  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1415  !! present, this parameter is not written to a doc file
1416  character(len=*), optional, intent(in) :: units !< The units of this parameter
1417  logical, optional, intent(in) :: default !< The default value of the parameter
1418  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1419  !! logged in the layout parameter file
1420  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1421  !! logged in the debugging parameter file
1422 
1423  character(len=240) :: mesg, myunits
1424 
1425  if (value) then
1426  write(mesg, '(" ",a," ",a,": True")') trim(modulename), trim(varname)
1427  else
1428  write(mesg, '(" ",a," ",a,": False")') trim(modulename), trim(varname)
1429  endif
1430  if (is_root_pe()) then
1431  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1432  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1433  endif
1434 
1435  myunits="Boolean"; if (present(units)) write(myunits(1:240),'(A)') trim(units)
1436  if (present(desc)) &
1437  call doc_param(cs%doc, varname, desc, myunits, value, default, &
1438  layoutparam=layoutparam, debuggingparam=debuggingparam)
1439 
1440 end subroutine log_param_logical
1441 
1442 !> Log the name and value of a character string model parameter in documentation files.
1443 subroutine log_param_char(CS, modulename, varname, value, desc, units, &
1444  default, layoutParam, debuggingParam)
1445  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1446  !! it is also a structure to parse for run-time parameters
1447  character(len=*), intent(in) :: modulename !< The name of the calling module
1448  character(len=*), intent(in) :: varname !< The name of the parameter to log
1449  character(len=*), intent(in) :: value !< The value of the parameter to log
1450  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1451  !! present, this parameter is not written to a doc file
1452  character(len=*), optional, intent(in) :: units !< The units of this parameter
1453  character(len=*), optional, intent(in) :: default !< The default value of the parameter
1454  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1455  !! logged in the layout parameter file
1456  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1457  !! logged in the debugging parameter file
1458 
1459  character(len=240) :: mesg, myunits
1460 
1461  write(mesg, '(" ",a," ",a,": ",a)') &
1462  trim(modulename), trim(varname), trim(value)
1463  if (is_root_pe()) then
1464  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1465  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1466  endif
1467 
1468  myunits=" "; if (present(units)) write(myunits(1:240),'(A)') trim(units)
1469  if (present(desc)) &
1470  call doc_param(cs%doc, varname, desc, myunits, value, default, &
1471  layoutparam=layoutparam, debuggingparam=debuggingparam)
1472 
1473 end subroutine log_param_char
1474 
1475 !> This subroutine writes the value of a time-type parameter to a log file,
1476 !! along with its name and the module it came from.
1477 subroutine log_param_time(CS, modulename, varname, value, desc, units, &
1478  default, timeunit, layoutParam, debuggingParam, log_date)
1479  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1480  !! it is also a structure to parse for run-time parameters
1481  character(len=*), intent(in) :: modulename !< The name of the calling module
1482  character(len=*), intent(in) :: varname !< The name of the parameter to log
1483  type(time_type), intent(in) :: value !< The value of the parameter to log
1484  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1485  !! present, this parameter is not written to a doc file
1486  character(len=*), optional, intent(in) :: units !< The units of this parameter
1487  type(time_type), optional, intent(in) :: default !< The default value of the parameter
1488  real, optional, intent(in) :: timeunit !< The number of seconds in a time unit for
1489  !! real-number output.
1490  logical, optional, intent(in) :: log_date !< If true, log the time_type in date format.
1491  !! If missing the default is false.
1492  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1493  !! logged in the layout parameter file
1494  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1495  !! logged in the debugging parameter file
1496 
1497  ! Local variables
1498  real :: real_time, real_default
1499  logical :: use_timeunit, date_format
1500  character(len=240) :: mesg, myunits
1501  character(len=80) :: date_string, default_string
1502  integer :: days, secs, ticks, ticks_per_sec
1503 
1504  use_timeunit = .false.
1505  date_format = .false. ; if (present(log_date)) date_format = log_date
1506 
1507  call get_time(value, secs, days, ticks)
1508 
1509  if (ticks == 0) then
1510  write(mesg, '(" ",a," ",a," (Time): ",i0,":",i0)') trim(modulename), &
1511  trim(varname), days, secs
1512  else
1513  write(mesg, '(" ",a," ",a," (Time): ",i0,":",i0,":",i0)') trim(modulename), &
1514  trim(varname), days, secs, ticks
1515  endif
1516  if (is_root_pe()) then
1517  if (cs%log_open) write(cs%stdlog,'(a)') trim(mesg)
1518  if (cs%log_to_stdout) write(cs%stdout,'(a)') trim(mesg)
1519  endif
1520 
1521  if (present(desc)) then
1522  if (present(timeunit)) use_timeunit = (timeunit > 0.0)
1523  if (date_format) then
1524  myunits='[date]'
1525 
1526  date_string = convert_date_to_string(value)
1527  if (present(default)) then
1528  default_string = convert_date_to_string(default)
1529  call doc_param(cs%doc, varname, desc, myunits, date_string, &
1530  default=default_string, layoutparam=layoutparam, &
1531  debuggingparam=debuggingparam)
1532  else
1533  call doc_param(cs%doc, varname, desc, myunits, date_string, &
1534  layoutparam=layoutparam, debuggingparam=debuggingparam)
1535  endif
1536  elseif (use_timeunit) then
1537  if (present(units)) then
1538  write(myunits(1:240),'(A)') trim(units)
1539  else
1540  if (abs(timeunit-1.0) < 0.01) then ; myunits = "seconds"
1541  elseif (abs(timeunit-3600.0) < 1.0) then ; myunits = "hours"
1542  elseif (abs(timeunit-86400.0) < 1.0) then ; myunits = "days"
1543  elseif (abs(timeunit-3.1e7) < 1.0e6) then ; myunits = "years"
1544  else ; write(myunits,'(es8.2," sec")') timeunit ; endif
1545  endif
1546  real_time = (86400.0/timeunit)*days + secs/timeunit
1547  if (ticks > 0) real_time = real_time + &
1548  real(ticks) / (timeunit*get_ticks_per_second())
1549  if (present(default)) then
1550  call get_time(default, secs, days, ticks)
1551  real_default = (86400.0/timeunit)*days + secs/timeunit
1552  if (ticks > 0) real_default = real_default + &
1553  real(ticks) / (timeunit*get_ticks_per_second())
1554  call doc_param(cs%doc, varname, desc, myunits, real_time, real_default)
1555  else
1556  call doc_param(cs%doc, varname, desc, myunits, real_time)
1557  endif
1558  else
1559  myunits='not defined'; if (present(units)) write(myunits(1:240),'(A)') trim(units)
1560  call doc_param(cs%doc, varname, desc, myunits, value, default)
1561  endif
1562  endif
1563 
1564 end subroutine log_param_time
1565 
1566 !> This function converts a date into a string, valid with ticks and for dates up to year 99,999,999
1567 function convert_date_to_string(date) result(date_string)
1568  type(time_type), intent(in) :: date !< The date to be translated into a string.
1569  character(len=40) :: date_string !< A date string in a format like YYYY-MM-DD HH:MM:SS.sss
1570 
1571  ! Local variables
1572  character(len=40) :: sub_string
1573  real :: real_secs
1574  integer :: yrs, mons, days, hours, mins, secs, ticks, ticks_per_sec
1575 
1576  call get_date(date, yrs, mons, days, hours, mins, secs, ticks)
1577  write (date_string, '(i8.4)') yrs
1578  write (sub_string, '("-", i2.2, "-", I2.2, " ", i2.2, ":", i2.2, ":")') &
1579  mons, days, hours, mins
1580  date_string = trim(adjustl(date_string)) // trim(sub_string)
1581  if (ticks > 0) then
1582  ticks_per_sec = get_ticks_per_second()
1583  real_secs = secs + ticks/ticks_per_sec
1584  if (ticks_per_sec <= 100) then
1585  write (sub_string, '(F7.3)') real_secs
1586  else
1587  write (sub_string, '(F10.6)') real_secs
1588  endif
1589  else
1590  write (sub_string, '(i2.2)') secs
1591  endif
1592  date_string = trim(date_string) // trim(adjustl(sub_string))
1593 
1594 end function convert_date_to_string
1595 
1596 !> This subroutine reads the value of an integer model parameter from a parameter file
1597 !! and logs it in documentation files.
1598 subroutine get_param_int(CS, modulename, varname, value, desc, units, &
1599  default, fail_if_missing, do_not_read, do_not_log, &
1600  static_value, layoutParam, debuggingParam)
1601  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1602  !! it is also a structure to parse for run-time parameters
1603  character(len=*), intent(in) :: modulename !< The name of the calling module
1604  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1605  integer, intent(inout) :: value !< The value of the parameter that may be
1606  !! read from the parameter file and logged
1607  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1608  !! present, this parameter is not written to a doc file
1609  character(len=*), optional, intent(in) :: units !< The units of this parameter
1610  integer, optional, intent(in) :: default !< The default value of the parameter
1611  integer, optional, intent(in) :: static_value !< If this parameter is static, it takes
1612  !! this value, which can be compared for consistency with
1613  !! what is in the parameter file.
1614  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1615  !! if this variable is not found in the parameter file
1616  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1617  !! value for this parameter, although it might be logged.
1618  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1619  !! parameter to the documentation files
1620  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1621  !! logged in the layout parameter file
1622  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1623  !! logged in the debugging parameter file
1624 
1625  logical :: do_read, do_log
1626 
1627  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1628  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1629 
1630  if (do_read) then
1631  if (present(default)) value = default
1632  if (present(static_value)) value = static_value
1633  call read_param_int(cs, varname, value, fail_if_missing)
1634  endif
1635 
1636  if (do_log) then
1637  call log_param_int(cs, modulename, varname, value, desc, units, &
1638  default, layoutparam, debuggingparam)
1639  endif
1640 
1641 end subroutine get_param_int
1642 
1643 !> This subroutine reads the values of an array of integer model parameters from a parameter file
1644 !! and logs them in documentation files.
1645 subroutine get_param_int_array(CS, modulename, varname, value, desc, units, &
1646  default, fail_if_missing, do_not_read, do_not_log, &
1647  static_value, layoutParam, debuggingParam)
1648  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1649  !! it is also a structure to parse for run-time parameters
1650  character(len=*), intent(in) :: modulename !< The name of the calling module
1651  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1652  integer, dimension(:), intent(inout) :: value !< The value of the parameter that may be reset
1653  !! from the parameter file
1654  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1655  !! present, this parameter is not written to a doc file
1656  character(len=*), optional, intent(in) :: units !< The units of this parameter
1657  integer, optional, intent(in) :: default !< The default value of the parameter
1658  integer, optional, intent(in) :: static_value !< If this parameter is static, it takes
1659  !! this value, which can be compared for consistency with
1660  !! what is in the parameter file.
1661  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1662  !! if this variable is not found in the parameter file
1663  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1664  !! value for this parameter, although it might be logged.
1665  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1666  !! parameter to the documentation files
1667  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1668  !! logged in the layout parameter file
1669  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1670  !! logged in the debugging parameter file
1671 
1672  logical :: do_read, do_log
1673 
1674  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1675  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1676 
1677  if (do_read) then
1678  if (present(default)) then ; value(:) = default ; endif
1679  if (present(static_value)) then ; value(:) = static_value ; endif
1680  call read_param_int_array(cs, varname, value, fail_if_missing)
1681  endif
1682 
1683  if (do_log) then
1684  call log_param_int_array(cs, modulename, varname, value, desc, &
1685  units, default, layoutparam, debuggingparam)
1686  endif
1687 
1688 end subroutine get_param_int_array
1689 
1690 !> This subroutine reads the value of a real model parameter from a parameter file
1691 !! and logs it in documentation files.
1692 subroutine get_param_real(CS, modulename, varname, value, desc, units, &
1693  default, fail_if_missing, do_not_read, do_not_log, &
1694  static_value, debuggingParam, scale, unscaled)
1695  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1696  !! it is also a structure to parse for run-time parameters
1697  character(len=*), intent(in) :: modulename !< The name of the calling module
1698  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1699  real, intent(inout) :: value !< The value of the parameter that may be
1700  !! read from the parameter file and logged
1701  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1702  !! present, this parameter is not written to a doc file
1703  character(len=*), optional, intent(in) :: units !< The units of this parameter
1704  real, optional, intent(in) :: default !< The default value of the parameter
1705  real, optional, intent(in) :: static_value !< If this parameter is static, it takes
1706  !! this value, which can be compared for consistency with
1707  !! what is in the parameter file.
1708  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1709  !! if this variable is not found in the parameter file
1710  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1711  !! value for this parameter, although it might be logged.
1712  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1713  !! parameter to the documentation files
1714  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1715  !! logged in the debugging parameter file
1716  real, optional, intent(in) :: scale !< A scaling factor that the parameter is
1717  !! multiplied by before it is returned.
1718  real, optional, intent(out) :: unscaled !< The value of the parameter that would be
1719  !! returned without any multiplication by a scaling factor.
1720 
1721  logical :: do_read, do_log
1722 
1723  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1724  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1725 
1726  if (do_read) then
1727  if (present(default)) value = default
1728  if (present(static_value)) value = static_value
1729  call read_param_real(cs, varname, value, fail_if_missing)
1730  endif
1731 
1732  if (do_log) then
1733  call log_param_real(cs, modulename, varname, value, desc, units, &
1734  default, debuggingparam)
1735  endif
1736 
1737  if (present(unscaled)) unscaled = value
1738  if (present(scale)) value = scale*value
1739 
1740 end subroutine get_param_real
1741 
1742 !> This subroutine reads the values of an array of real model parameters from a parameter file
1743 !! and logs them in documentation files.
1744 subroutine get_param_real_array(CS, modulename, varname, value, desc, units, &
1745  default, fail_if_missing, do_not_read, do_not_log, debuggingParam, &
1746  static_value, scale, unscaled)
1747  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1748  !! it is also a structure to parse for run-time parameters
1749  character(len=*), intent(in) :: modulename !< The name of the calling module
1750  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1751  real, dimension(:), intent(inout) :: value !< The value of the parameter that may be
1752  !! read from the parameter file and logged
1753  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1754  !! present, this parameter is not written to a doc file
1755  character(len=*), optional, intent(in) :: units !< The units of this parameter
1756  real, optional, intent(in) :: default !< The default value of the parameter
1757  real, optional, intent(in) :: static_value !< If this parameter is static, it takes
1758  !! this value, which can be compared for consistency with
1759  !! what is in the parameter file.
1760  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1761  !! if this variable is not found in the parameter file
1762  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1763  !! value for this parameter, although it might be logged.
1764  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1765  !! parameter to the documentation files
1766  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1767  !! logged in the debugging parameter file
1768  real, optional, intent(in) :: scale !< A scaling factor that the parameter is
1769  !! multiplied by before it is returned.
1770  real, dimension(:), optional, intent(out) :: unscaled !< The value of the parameter that would be
1771  !! returned without any multiplication by a scaling factor.
1772 
1773  logical :: do_read, do_log
1774 
1775  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1776  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1777 
1778  if (do_read) then
1779  if (present(default)) then ; value(:) = default ; endif
1780  if (present(static_value)) then ; value(:) = static_value ; endif
1781  call read_param_real_array(cs, varname, value, fail_if_missing)
1782  endif
1783 
1784  if (do_log) then
1785  call log_param_real_array(cs, modulename, varname, value, desc, &
1786  units, default, debuggingparam)
1787  endif
1788 
1789  if (present(unscaled)) unscaled(:) = value(:)
1790  if (present(scale)) value(:) = scale*value(:)
1791 
1792 end subroutine get_param_real_array
1793 
1794 !> This subroutine reads the value of a character string model parameter from a parameter file
1795 !! and logs it in documentation files.
1796 subroutine get_param_char(CS, modulename, varname, value, desc, units, &
1797  default, fail_if_missing, do_not_read, do_not_log, &
1798  static_value, layoutParam, debuggingParam)
1799  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1800  !! it is also a structure to parse for run-time parameters
1801  character(len=*), intent(in) :: modulename !< The name of the calling module
1802  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1803  character(len=*), intent(inout) :: value !< The value of the parameter that may be
1804  !! read from the parameter file and logged
1805  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1806  !! present, this parameter is not written to a doc file
1807  character(len=*), optional, intent(in) :: units !< The units of this parameter
1808  character(len=*), optional, intent(in) :: default !< The default value of the parameter
1809  character(len=*), optional, intent(in) :: static_value !< If this parameter is static, it takes
1810  !! this value, which can be compared for consistency with
1811  !! what is in the parameter file.
1812  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1813  !! if this variable is not found in the parameter file
1814  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1815  !! value for this parameter, although it might be logged.
1816  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1817  !! parameter to the documentation files
1818  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1819  !! logged in the layout parameter file
1820  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1821  !! logged in the debugging parameter file
1822 
1823  logical :: do_read, do_log
1824 
1825  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1826  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1827 
1828  if (do_read) then
1829  if (present(default)) value = default
1830  if (present(static_value)) value = static_value
1831  call read_param_char(cs, varname, value, fail_if_missing)
1832  endif
1833 
1834  if (do_log) then
1835  call log_param_char(cs, modulename, varname, value, desc, units, &
1836  default, layoutparam, debuggingparam)
1837  endif
1838 
1839 end subroutine get_param_char
1840 
1841 !> This subroutine reads the values of an array of character string model parameters
1842 !! from a parameter file and logs them in documentation files.
1843 subroutine get_param_char_array(CS, modulename, varname, value, desc, units, &
1844  default, fail_if_missing, do_not_read, do_not_log, static_value)
1845  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1846  !! it is also a structure to parse for run-time parameters
1847  character(len=*), intent(in) :: modulename !< The name of the calling module
1848  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1849  character(len=*), dimension(:), intent(inout) :: value !< The value of the parameter that may be
1850  !! read from the parameter file and logged
1851  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1852  !! present, this parameter is not written to a doc file
1853  character(len=*), optional, intent(in) :: units !< The units of this parameter
1854  character(len=*), optional, intent(in) :: default !< The default value of the parameter
1855  character(len=*), optional, intent(in) :: static_value !< If this parameter is static, it takes
1856  !! this value, which can be compared for consistency with
1857  !! what is in the parameter file.
1858  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1859  !! if this variable is not found in the parameter file
1860  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1861  !! value for this parameter, although it might be logged.
1862  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1863  !! parameter to the documentation files
1864 
1865  ! Local variables
1866  logical :: do_read, do_log
1867  integer :: i, len_tot, len_val
1868  character(len=240) :: cat_val
1869 
1870  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1871  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1872 
1873  if (do_read) then
1874  if (present(default)) then ; value(:) = default ; endif
1875  if (present(static_value)) then ; value(:) = static_value ; endif
1876  call read_param_char_array(cs, varname, value, fail_if_missing)
1877  endif
1878 
1879  if (do_log) then
1880  cat_val = trim(value(1)); len_tot = len_trim(value(1))
1881  do i=2,size(value)
1882  len_val = len_trim(value(i))
1883  if ((len_val > 0) .and. (len_tot + len_val + 2 < 240)) then
1884  cat_val = trim(cat_val)//achar(34)// ", "//achar(34)//trim(value(i))
1885  len_tot = len_tot + len_val
1886  endif
1887  enddo
1888  call log_param_char(cs, modulename, varname, cat_val, desc, &
1889  units, default)
1890  endif
1891 
1892 end subroutine get_param_char_array
1893 
1894 !> This subroutine reads the value of a logical model parameter from a parameter file
1895 !! and logs it in documentation files.
1896 subroutine get_param_logical(CS, modulename, varname, value, desc, units, &
1897  default, fail_if_missing, do_not_read, do_not_log, &
1898  static_value, layoutParam, debuggingParam)
1899  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1900  !! it is also a structure to parse for run-time parameters
1901  character(len=*), intent(in) :: modulename !< The name of the calling module
1902  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1903  logical, intent(inout) :: value !< The value of the parameter that may be
1904  !! read from the parameter file and logged
1905  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1906  !! present, this parameter is not written to a doc file
1907  character(len=*), optional, intent(in) :: units !< The units of this parameter
1908  logical, optional, intent(in) :: default !< The default value of the parameter
1909  logical, optional, intent(in) :: static_value !< If this parameter is static, it takes
1910  !! this value, which can be compared for consistency with
1911  !! what is in the parameter file.
1912  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1913  !! if this variable is not found in the parameter file
1914  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1915  !! value for this parameter, although it might be logged.
1916  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1917  !! parameter to the documentation files
1918  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1919  !! logged in the layout parameter file
1920  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1921  !! logged in the debugging parameter file
1922 
1923  logical :: do_read, do_log
1924 
1925  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1926  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1927 
1928  if (do_read) then
1929  if (present(default)) value = default
1930  if (present(static_value)) value = static_value
1931  call read_param_logical(cs, varname, value, fail_if_missing)
1932  endif
1933 
1934  if (do_log) then
1935  call log_param_logical(cs, modulename, varname, value, desc, &
1936  units, default, layoutparam, debuggingparam)
1937  endif
1938 
1939 end subroutine get_param_logical
1940 
1941 !> This subroutine reads the value of a time-type model parameter from a parameter file
1942 !! and logs it in documentation files.
1943 subroutine get_param_time(CS, modulename, varname, value, desc, units, &
1944  default, fail_if_missing, do_not_read, do_not_log, &
1945  timeunit, static_value, layoutParam, debuggingParam, &
1946  log_as_date)
1947  type(param_file_type), intent(in) :: CS !< The control structure for the file_parser module,
1948  !! it is also a structure to parse for run-time parameters
1949  character(len=*), intent(in) :: modulename !< The name of the calling module
1950  character(len=*), intent(in) :: varname !< The case-sensitive name of the parameter to read
1951  type(time_type), intent(inout) :: value !< The value of the parameter that may be
1952  !! read from the parameter file and logged
1953  character(len=*), optional, intent(in) :: desc !< A description of this variable; if not
1954  !! present, this parameter is not written to a doc file
1955  character(len=*), optional, intent(in) :: units !< The units of this parameter
1956  type(time_type), optional, intent(in) :: default !< The default value of the parameter
1957  type(time_type), optional, intent(in) :: static_value !< If this parameter is static, it takes
1958  !! this value, which can be compared for consistency with
1959  !! what is in the parameter file.
1960  logical, optional, intent(in) :: fail_if_missing !< If present and true, a fatal error occurs
1961  !! if this variable is not found in the parameter file
1962  logical, optional, intent(in) :: do_not_read !< If present and true, do not read a
1963  !! value for this parameter, although it might be logged.
1964  logical, optional, intent(in) :: do_not_log !< If present and true, do not log this
1965  !! parameter to the documentation files
1966  real, optional, intent(in) :: timeunit !< The number of seconds in a time unit for
1967  !! real-number input to be translated to a time.
1968  logical, optional, intent(in) :: layoutParam !< If present and true, this parameter is
1969  !! logged in the layout parameter file
1970  logical, optional, intent(in) :: debuggingParam !< If present and true, this parameter is
1971  !! logged in the debugging parameter file
1972  logical, optional, intent(in) :: log_as_date !< If true, log the time_type in date
1973  !! format. The default is false.
1974 
1975  logical :: do_read, do_log, date_format, log_date
1976 
1977  do_read = .true. ; if (present(do_not_read)) do_read = .not.do_not_read
1978  do_log = .true. ; if (present(do_not_log)) do_log = .not.do_not_log
1979  log_date = .false.
1980 
1981  if (do_read) then
1982  if (present(default)) value = default
1983  if (present(static_value)) value = static_value
1984  call read_param_time(cs, varname, value, timeunit, fail_if_missing, date_format=log_date)
1985  endif
1986 
1987  if (do_log) then
1988  if (present(log_as_date)) log_date = log_as_date
1989  call log_param_time(cs, modulename, varname, value, desc, units, default, &
1990  timeunit, layoutparam=layoutparam, &
1991  debuggingparam=debuggingparam, log_date=log_date)
1992  endif
1993 
1994 end subroutine get_param_time
1995 
1996 ! -----------------------------------------------------------------------------
1997 
1998 !> Resets the parameter block name to blank
1999 subroutine clearparameterblock(CS)
2000  type(param_file_type), intent(in) :: cs !< The control structure for the file_parser module,
2001  !! it is also a structure to parse for run-time parameters
2002 
2003  type(parameter_block), pointer :: block => null()
2004  if (associated(cs%blockName)) then
2005  block => cs%blockName
2006  block%name = ''
2007  else
2008  if (is_root_pe()) call mom_error(fatal, &
2009  'clearParameterBlock: A clear was attempted before allocation.')
2010  endif
2011 end subroutine clearparameterblock
2012 
2013 !> Tags blockName onto the end of the active parameter block name
2014 subroutine openparameterblock(CS,blockName,desc)
2015  type(param_file_type), intent(in) :: cs !< The control structure for the file_parser module,
2016  !! it is also a structure to parse for run-time parameters
2017  character(len=*), intent(in) :: blockname !< The name of a parameter block being added
2018  character(len=*), optional, intent(in) :: desc !< A description of the parameter block being added
2019 
2020  type(parameter_block), pointer :: block => null()
2021  if (associated(cs%blockName)) then
2022  block => cs%blockName
2023  block%name = pushblocklevel(block%name,blockname)
2024  call doc_openblock(cs%doc,block%name,desc)
2025  else
2026  if (is_root_pe()) call mom_error(fatal, &
2027  'openParameterBlock: A push was attempted before allocation.')
2028  endif
2029 end subroutine openparameterblock
2030 
2031 !> Remove the lowest level of recursion from the active block name
2032 subroutine closeparameterblock(CS)
2033  type(param_file_type), intent(in) :: cs !< The control structure for the file_parser module,
2034  !! it is also a structure to parse for run-time parameters
2035 
2036  type(parameter_block), pointer :: block => null()
2037 
2038  if (associated(cs%blockName)) then
2039  block => cs%blockName
2040  if (is_root_pe().and.len_trim(block%name)==0) call mom_error(fatal, &
2041  'closeParameterBlock: A pop was attempted on an empty stack. ("'//&
2042  trim(block%name)//'")')
2043  call doc_closeblock(cs%doc,block%name)
2044  else
2045  if (is_root_pe()) call mom_error(fatal, &
2046  'closeParameterBlock: A pop was attempted before allocation.')
2047  endif
2048  block%name = popblocklevel(block%name)
2049 end subroutine closeparameterblock
2050 
2051 !> Extends block name (deeper level of parameter block)
2052 function pushblocklevel(oldblockName,newBlockName)
2053  character(len=*), intent(in) :: oldblockname !< A sequence of hierarchical parameter block names
2054  character(len=*), intent(in) :: newblockname !< A new block name to add to the end of the sequence
2055  character(len=len(oldBlockName)+40) :: pushblocklevel
2056 
2057  if (len_trim(oldblockname)>0) then
2058  pushblocklevel=trim(oldblockname)//'%'//trim(newblockname)
2059  else
2060  pushblocklevel=trim(newblockname)
2061  endif
2062 end function pushblocklevel
2063 
2064 !> Truncates block name (shallower level of parameter block)
2065 function popblocklevel(oldblockName)
2066  character(len=*), intent(in) :: oldblockname !< A sequence of hierarchical parameter block names
2067  character(len=len(oldBlockName)+40) :: popblocklevel
2068 
2069  integer :: i
2070  i = index(trim(oldblockname), '%', .true.)
2071  if (i>1) then
2072  popblocklevel = trim(oldblockname(1:i-1))
2073  elseif (i==0) then
2074  popblocklevel = ''
2075  else ! i==1
2076  if (is_root_pe()) call mom_error(fatal, &
2077  'popBlockLevel: A pop was attempted leaving an empty block name.')
2078  endif
2079 end function popblocklevel
2080 
2081 !> \namespace mom_file_parser
2082 !!
2083 !! By Robert Hallberg and Alistair Adcroft, updated 9/2013.
2084 !!
2085 !! The subroutines here parse a set of input files for the value
2086 !! a named parameter and sets that parameter at run time. Currently
2087 !! these files use use one of several formats:
2088 !! \#define VAR ! To set the logical VAR to true.
2089 !! VAR = True ! To set the logical VAR to true.
2090 !! \#undef VAR ! To set the logical VAR to false.
2091 !! VAR = False ! To set the logical VAR to false.
2092 !! \#define VAR 999 ! To set the real or integer VAR to 999.
2093 !! VAR = 999 ! To set the real or integer VAR to 999.
2094 !! \#override VAR = 888 ! To override a previously set value.
2095 !! VAR = 1.1, 2.2, 3.3 ! To set an array of real values.
2096  ! Note that in the comments above, dOxygen translates \# to # .
2097 !!
2098 !! In addition, when set by the get_param interface, the values of
2099 !! parameters are automatically logged, along with defaults, units,
2100 !! and a description. It is an error for a variable to be overridden
2101 !! more than once, and MOM6 has a facility to check for unused lines
2102 !! to set variables, which may indicate miss-spelled or archaic
2103 !! parameters. Parameter names are case-specific, and lines may use
2104 !! a F90 or C++ style comment, starting with ! or //.
2105 
2106 end module mom_file_parser
mom_time_manager
Wraps the FMS time manager functions.
Definition: MOM_time_manager.F90:2
mom_document::doc_param
Document parameter values.
Definition: MOM_document.F90:16
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
mom_file_parser::file_data_type
The valid lines extracted from an input parameter file without comments.
Definition: MOM_file_parser.F90:35
mom_string_functions
Handy functions for manipulating strings.
Definition: MOM_string_functions.F90:2
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_coms
Interfaces to non-domain-oriented communication subroutines, including the MOM6 reproducing sums faci...
Definition: MOM_coms.F90:3
mom_file_parser::parameter_block
Specify the active parameter block.
Definition: MOM_file_parser.F90:49
mom_document
The subroutines here provide hooks for document generation functions at various levels of granularity...
Definition: MOM_document.F90:3
mom_document::doc_type
A structure that controls where the documentation occurs, its veborsity and formatting.
Definition: MOM_document.F90:28
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_file_parser::log_param
An overloaded interface to log the values of various types of parameters.
Definition: MOM_file_parser.F90:96
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom_file_parser::read_param
An overloaded interface to read various types of parameters.
Definition: MOM_file_parser.F90:90