ROMS
Loading...
Searching...
No Matches
get_metadata.F
Go to the documentation of this file.
1#include "cppdefs.h"
3!
4!git $Id$
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2025 The ROMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.md !
9!=======================================================================
10! !
11! This module has functions to process ROMS I/O metadata or coupling !
12! metadata files. Two formats are supported: native and YAML files. !
13! The native format is deprecated since YAML files are expandable and !
14! portable. !
15! !
16! io_metadata It processes entries in ROMS input/output !
17! variables metadata: !
18! !
19! 'varinfo.dat' or 'varinfo.yaml' !
20! !
21! coupling_metadata It processes dictionary entries for the !
22! ESMF/NUOPC coupling system: !
23! !
24! 'coupling_*.dat' or 'coupling_*.yaml' !
25! !
26!=======================================================================
27!
28 USE mod_kinds, ONLY : dp
29 USE mod_parallel, ONLY : master
30 USE mod_iounits, ONLY : stdout, varname
31 USE mod_scalars, ONLY : exit_flag, noerror
33 USE yaml_parser_mod, ONLY : yaml_initialize, &
34 & yaml_get, &
35 & yaml_svec, &
36 & yaml_tree
37!
38 implicit none
39!
40!-----------------------------------------------------------------------
41! Define generic coupling field to process import and export states.
42!-----------------------------------------------------------------------
43!
45 logical :: connected
46 logical :: debug_write
47!
48 real(dp) :: add_offset
49 real(dp) :: scale
50!
51 character (len=:), allocatable :: connected_to
52 character (len=:), allocatable :: data_netcdf_vname
53 character (len=:), allocatable :: data_netcdf_tname
54 character (len=:), allocatable :: destination_grid
55 character (len=:), allocatable :: destination_units
56 character (len=:), allocatable :: extrapolate_method
57 character (len=:), allocatable :: long_name
58 character (len=:), allocatable :: map_norm
59 character (len=:), allocatable :: map_type
60 character (len=:), allocatable :: regrid_method
61 character (len=:), allocatable :: source_units
62 character (len=:), allocatable :: source_grid
63 character (len=:), allocatable :: short_name
64 character (len=:), allocatable :: standard_name
65!
66 END TYPE couplingfield
67!
68!-----------------------------------------------------------------------
69! Define generic YAML dictionary, containers, and counters used
70! during processing.
71!-----------------------------------------------------------------------
72!
73! YAML dictionary object. It is destroyed after processing, so it
74! can be reused to operate on other input YAML files.
75!
76 TYPE (yaml_tree) :: yml
77!
78! Metadata debugging and reporting switches
79!
80#ifdef METADATA_REPORT
81 logical :: ldebugmetadata = .true.
82 logical :: lreportyaml = .true.
83#else
84 logical :: ldebugmetadata = .false.
85 logical :: lreportyaml = .false.
86#endif
87!
88! Counters.
89!
90 integer :: ientry ! entry counter
91 integer :: nentries ! number of entries
92!
93! logical scalar dummy values.
94!
95 logical, allocatable :: ylogical1(:)
96!
97! Real scalar dummy values.
98!
99 real(dp), allocatable :: yreal1(:)
100 real(dp), allocatable :: yreal2(:)
101!
102! Derived-type dummy structures for processing string value or set
103! of values from a sequence flow, [val1, ..., valN].
104!
105 TYPE (yaml_svec), allocatable :: ystring1 (:)
106 TYPE (yaml_svec), allocatable :: ystring2 (:)
107 TYPE (yaml_svec), allocatable :: ystring3 (:)
108 TYPE (yaml_svec), allocatable :: ystring4 (:)
109 TYPE (yaml_svec), allocatable :: ystring5 (:)
110 TYPE (yaml_svec), allocatable :: ystring6 (:)
111 TYPE (yaml_svec), allocatable :: ystring7 (:)
112 TYPE (yaml_svec), allocatable :: ystring8 (:)
113 TYPE (yaml_svec), allocatable :: ystring9 (:)
114 TYPE (yaml_svec), allocatable :: ystring10(:)
115 TYPE (yaml_svec), allocatable :: ystring11(:)
116 TYPE (yaml_svec), allocatable :: ystring12(:)
117!
118 PUBLIC :: cmeps_metadata
119 PUBLIC :: coupling_metadata
120 PUBLIC :: io_metadata
121 PUBLIC :: metadata_has
122!
123!-----------------------------------------------------------------------
124 CONTAINS
125!-----------------------------------------------------------------------
126!
127 SUBROUTINE cmeps_metadata (self, filename, key, S)
128!
129!=======================================================================
130! !
131! It process either import or export fields which are stored as block !
132! lists (leading key/value is hyphenated) in the YAML file. The YAML !
133! file is used to configure ROMS ESMF/NUOPC 'cap' module to be run by !
134! the Community Mediator for Earth Prediction Systems (CMEPS). !
135! !
136! On Input: !
137! !
138! self YAML tree dictionary (TYPE yaml_tree) !
139! !
140! filename ROMS YAML configuration filename for CMEPS (string) !
141! !
142! key Leading blocking key to process (string), for example: !
143! 'export', 'import', or 'bulk_flux import' !
144! !
145! On Output: !
146! !
147! S Import or Export coupling fields (TYPE CouplingField) !
148! !
149!=======================================================================
150!
151! Imported variable declarations.
152!
153 TYPE (yaml_tree), intent(inout) :: self
154 character (len=*), intent(in ) :: filename
155 character (len=*), intent(in ) :: key
156 TYPE (couplingfield), allocatable, intent(out) :: s(:)
157!
158! Local variable declarations.
159!
160 integer :: i
161!
162 character (len=*), parameter :: myfile = &
163 & __FILE__//", cmeps_metadata"
164!
165!-----------------------------------------------------------------------
166! Process coupling import or export metadata for CMEPS.
167!-----------------------------------------------------------------------
168!
169! If applicable, create YAML tree dictionary.
170!
171 IF (.not.ASSOCIATED(self%list)) THEN
172 IF (founderror(yaml_initialize(self, trim(filename), &
173 & lreportyaml), &
174 & noerror, __line__, myfile)) THEN
175 IF (master) WRITE (stdout,10) trim(filename)
176 RETURN
177 END IF
178 END IF
179!
180! Extract requested blocking list.
181!
182 IF (founderror(yaml_get(self, trim(key)//'.standard_name', &
183 & ystring1), &
184 & noerror, __line__, myfile)) RETURN
185 nentries=SIZE(ystring1)
186!
187 IF (founderror(yaml_get(self, trim(key)//'.long_name', &
188 & ystring2), &
189 & noerror, __line__, myfile)) RETURN
190!
191 IF (founderror(yaml_get(self, trim(key)//'.short_name', &
192 & ystring3), &
193 & noerror, __line__, myfile)) RETURN
194!
195 IF (founderror(yaml_get(self, trim(key)//'.data_variables', &
196 & ystring4), &
197 & noerror, __line__, myfile)) RETURN
198!
199 IF (founderror(yaml_get(self, trim(key)//'.source_units', &
200 & ystring5), &
201 & noerror, __line__, myfile)) RETURN
202!
203 IF (founderror(yaml_get(self, trim(key)//'.destination_units', &
204 & ystring6), &
205 & noerror, __line__, myfile)) RETURN
206!
207 IF (founderror(yaml_get(self, trim(key)//'.source_grid', &
208 & ystring7), &
209 & noerror, __line__, myfile)) RETURN
210!
211 IF (founderror(yaml_get(self, trim(key)//'.destination_grid', &
212 & ystring8), &
213 & noerror, __line__, myfile)) RETURN
214!
215 IF (founderror(yaml_get(self, trim(key)//'.connected_to', &
216 & ystring9), &
217 & noerror, __line__, myfile)) RETURN
218!
219 IF (founderror(yaml_get(self, trim(key)//'.map_type', &
220 & ystring10), &
221 & noerror, __line__, myfile)) RETURN
222!
223 IF (founderror(yaml_get(self, trim(key)//'.map_norm', &
224 & ystring11), &
225 & noerror, __line__, myfile)) RETURN
226!
227 IF (.not.allocated(yreal1)) THEN
228 allocate ( yreal1(nentries) )
229 END IF
230 IF (founderror(yaml_get(self, trim(key)//'.add_offset', &
231 & yreal1), &
232 & noerror, __line__, myfile)) RETURN
233!
234 IF (.not.allocated(yreal2)) THEN
235 allocate ( yreal2(nentries) )
236 END IF
237 IF (founderror(yaml_get(self, trim(key)//'.scale', &
238 & yreal2), &
239 & noerror, __line__, myfile)) RETURN
240 IF (.not.allocated(yreal1)) THEN
241 allocate ( yreal1(nentries) )
242 END IF
243!
244 IF (.not.allocated(ylogical1)) THEN
245 allocate ( ylogical1(nentries) )
246 END IF
247 IF (founderror(yaml_get(self, trim(key)//'.debug_write', &
248 & ylogical1), &
249 & noerror, __line__, myfile)) RETURN
250!
251! Load metadata into output structure.
252!
253 IF (.not.allocated(s)) allocate ( s(nentries) )
254!
255 DO i=1,nentries
256 s(i)%debug_write = ylogical1(i)
257 s(i)%add_offset = yreal1(i)
258 s(i)%scale = yreal2(i)
259!
260 IF (founderror(assign_string(s(i)%standard_name, &
261 & ystring1(i)%value), &
262 & noerror, __line__, myfile)) RETURN
263!
264 IF (founderror(assign_string(s(i)%long_name, &
265 & ystring2(i)%value), &
266 & noerror, __line__, myfile)) RETURN
267!
268 IF (founderror(assign_string(s(i)%short_name, &
269 & ystring3(i)%value), &
270 & noerror, __line__, myfile)) RETURN
271!
272 IF (founderror(assign_string(s(i)%data_netcdf_vname, &
273 & ystring4(i)%vector(1)%value), &
274 & noerror, __line__, myfile)) RETURN
275!
276 IF (founderror(assign_string(s(i)%data_netcdf_tname, &
277 & ystring4(i)%vector(2)%value), &
278 & noerror, __line__, myfile)) RETURN
279!
280 IF (founderror(assign_string(s(i)%source_units, &
281 & ystring5(i)%value), &
282 & noerror, __line__, myfile)) RETURN
283!
284 IF (founderror(assign_string(s(i)%destination_units, &
285 & ystring6(i)%value), &
286 & noerror, __line__, myfile)) RETURN
287!
288 IF (founderror(assign_string(s(i)%source_grid, &
289 & ystring7(i)%value), &
290 & noerror, __line__, myfile)) RETURN
291!
292 IF (founderror(assign_string(s(i)%destination_grid, &
293 & ystring8(i)%value), &
294 & noerror, __line__, myfile)) RETURN
295!
296 IF (founderror(assign_string(s(i)%connected_to, &
297 & ystring9(i)%value), &
298 & noerror, __line__, myfile)) RETURN
299 IF (lowercase(s(i)%connected_to).eq.'false') THEN
300 s(i)%connected=.false.
301 ELSE
302 s(i)%connected=.true.
303 END IF
304!
305 IF (founderror(assign_string(s(i)%map_type, &
306 & ystring10(i)%value), &
307 & noerror, __line__, myfile)) RETURN
308!
309 IF (founderror(assign_string(s(i)%map_norm, &
310 & ystring11(i)%value), &
311 & noerror, __line__, myfile)) RETURN
312 END DO
313!
314! Deallocate generic structures.
315!
316 IF (allocated(ystring1 )) deallocate (ystring1 )
317 IF (allocated(ystring2 )) deallocate (ystring2 )
318 IF (allocated(ystring3 )) deallocate (ystring3 )
319 IF (allocated(ystring4 )) deallocate (ystring4 )
320 IF (allocated(ystring5 )) deallocate (ystring5 )
321 IF (allocated(ystring6 )) deallocate (ystring6 )
322 IF (allocated(ystring7 )) deallocate (ystring7 )
323 IF (allocated(ystring8 )) deallocate (ystring8 )
324 IF (allocated(ystring9 )) deallocate (ystring9 )
325 IF (allocated(ystring10)) deallocate (ystring10)
326 IF (allocated(ystring11)) deallocate (ystring11)
327 IF (allocated(ylogical1)) deallocate (ylogical1)
328 IF (allocated(yreal1)) deallocate (yreal1)
329 IF (allocated(yreal2)) deallocate (yreal2)
330!
331! Report.
332!
333 IF (master.and.ldebugmetadata) THEN
334 WRITE (stdout,'(/,3a,/,3a)') &
335 & "Coupling Metadata Dictionary, key: '", trim(key), "',", &
336 & repeat('=',28), ' File: ', trim(filename)
337 DO i=1,SIZE(s)
338 WRITE (stdout,'(/,a,a)') ' - standard_name: ', &
339 & trim(s(i)%standard_name)
340 WRITE (stdout,'(a,a)') ' long_name: ', &
341 & trim(s(i)%long_name)
342 WRITE (stdout,'(a,a)') ' short_name: ', &
343 & trim(s(i)%short_name)
344 WRITE (stdout,'(a,a)') ' data_netcdf_variable: ', &
345 & trim(s(i)%data_netcdf_vname)
346 WRITE (stdout,'(a,a)') ' data_netcdf_time: ', &
347 & trim(s(i)%data_netcdf_tname)
348 WRITE (stdout,'(a,a)') ' source_units: ', &
349 & trim(s(i)%source_units)
350 WRITE (stdout,'(a,a)') ' destination_units: ', &
351 & trim(s(i)%destination_units)
352 WRITE (stdout,'(a,a)') ' source_grid: ', &
353 & trim(s(i)%source_grid)
354 WRITE (stdout,'(a,a)') ' destination_grid: ', &
355 & trim(s(i)%destination_grid)
356 WRITE (stdout,'(a,1p,e15.8)') ' add_offset: ', &
357 & s(i)%add_offset
358 WRITE (stdout,'(a,1p,e15.8)') ' scale: ', &
359 & s(i)%scale
360 WRITE (stdout,'(a,l1)') ' debug_write: ', &
361 & s(i)%debug_write
362 WRITE (stdout,'(a,l1)') ' connected: ', &
363 & s(i)%connected
364 WRITE (stdout,'(a,a)') ' connected_to: ', &
365 & trim(s(i)%connected_to)
366 WRITE (stdout,'(a,a)') ' map_type: ', &
367 & trim(s(i)%map_type)
368 WRITE (stdout,'(a,a)') ' map_norm: ', &
369 & trim(s(i)%map_norm)
370 END DO
371 FLUSH (stdout)
372 END IF
373!
374 10 FORMAT (/,' CMEPS_METADATA - Unable to create YAML object for', &
375 & ' ROMS/CMEPS configuration metadata file: ',/,21x,a,/, &
376 & 21x,'Default file is located in source directory.')
377!
378 RETURN
379 END SUBROUTINE cmeps_metadata
380!
381 SUBROUTINE coupling_metadata (filename, S)
382!
383!=======================================================================
384! !
385! It processes import and export field dictionary for ROMS coupling !
386! system with the ESMF/NUOPC library. If processes field metadata !
387! entry-by-entry from 'coupling_*.dat' or 'coupling_*.yaml'. !
388! !
389! On Input: !
390! !
391! filename Coupling metadata filename (string) !
392! !
393! On Output: !
394! !
395! S Import/Export coupling fields (TYPE CouplingField) !
396! !
397!=======================================================================
398!
399! Imported variable declarations.
400!
401 character (len=*), intent(in) :: filename
402!
403 TYPE (couplingfield), allocatable, intent(out) :: s(:)
404!
405! Local variable declarations.
406!
407 logical :: isdat, isyaml, connected, debug_write
408!
409 real(dp) :: add_offset, scale
410!
411 integer, parameter :: iunit = 10
412 integer :: idot, lstr, lvar, i, io_err
413!
414 character (len=40 ) :: smodel, tname
415 character (len=100) :: cinfo(12)
416 character (len=256) :: io_errmsg
417
418 character (len=*), parameter :: myfile = &
419 & __FILE__//", coupling_metadata"
420!
421!-----------------------------------------------------------------------
422! Process coupling import/export metadata.
423!-----------------------------------------------------------------------
424!
425! Determine metadata file extension: 'coupling_*.dat' or
426! 'coupling_*.yaml'
427!
428 isdat =.false.
429 isyaml=.false.
430
431 lstr=len_trim(filename)
432 idot=index(filename(1:lstr), char(46), back=.true.)
433!
434 SELECT CASE (lowercase(filename(idot+1:lstr)))
435 CASE ('dat')
436 isdat=.true.
437 CASE ('yaml', 'yml')
438 isyaml=.true.
439 END SELECT
440!
441! If YAML metadata, create dictionary.
442!
443 IF (isyaml) THEN
444 ientry=0
445!
446 IF (founderror(yaml_initialize(yml, trim(filename), &
447 & lreportyaml), &
448 & noerror, __line__, myfile)) THEN
449 IF (master) WRITE (stdout,30) trim(filename)
450 RETURN
451 END IF
452!
453! If YAML metadata, extract key/value pair (blocking list).
454!
455 IF (founderror(yaml_get(yml, 'metadata.standard_name', &
456 & ystring1), &
457 & noerror, __line__, myfile)) RETURN
458 nentries=SIZE(ystring1)
459!
460 IF (founderror(yaml_get(yml, 'metadata.long_name', &
461 & ystring2), &
462 & noerror, __line__, myfile)) RETURN
463!
464 IF (founderror(yaml_get(yml, 'metadata.short_name', &
465 & ystring3), &
466 & noerror, __line__, myfile)) RETURN
467!
468 IF (founderror(yaml_get(yml, 'metadata.data_variables', &
469 & ystring4), &
470 & noerror, __line__, myfile)) RETURN
471!
472 IF (founderror(yaml_get(yml, 'metadata.source_units', &
473 & ystring5), &
474 & noerror, __line__, myfile)) RETURN
475!
476 IF (founderror(yaml_get(yml, 'metadata.destination_units', &
477 & ystring6), &
478 & noerror, __line__, myfile)) RETURN
479!
480 IF (founderror(yaml_get(yml, 'metadata.source_grid', &
481 & ystring7), &
482 & noerror, __line__, myfile)) RETURN
483!
484 IF (founderror(yaml_get(yml, 'metadata.destination_grid', &
485 & ystring8), &
486 & noerror, __line__, myfile)) RETURN
487!
488 IF (founderror(yaml_get(yml, 'metadata.connected_to', &
489 & ystring9), &
490 & noerror, __line__, myfile)) RETURN
491!
492 IF (founderror(yaml_get(yml, 'metadata.regrid_method', &
493 & ystring10), &
494 & noerror, __line__, myfile)) RETURN
495!
496 IF (founderror(yaml_get(yml, 'metadata.extrapolate_method', &
497 & ystring11), &
498 & noerror, __line__, myfile)) RETURN
499!
500 IF (allocated(yreal1)) deallocate (yreal1)
501 allocate ( yreal1(nentries) )
502 IF (founderror(yaml_get(yml, 'metadata.add_offset', &
503 & yreal1), &
504 & noerror, __line__, myfile)) RETURN
505!
506 IF (allocated(yreal2)) deallocate (yreal2)
507 allocate ( yreal2(nentries) )
508 IF (founderror(yaml_get(yml, 'metadata.scale', &
509 & yreal2), &
510 & noerror, __line__, myfile)) RETURN
511!
512 IF (allocated(ylogical1)) deallocate (ylogical1)
513 allocate ( ylogical1(nentries) )
514 IF (founderror(yaml_get(yml, 'metadata.debug_write', &
515 & ylogical1), &
516 & noerror, __line__, myfile)) RETURN
517!
518! Otherwise, open deprecated 'coupling_*.dat' file.
519!
520 ELSE IF (isdat) THEN
521 OPEN (unit=iunit, file=trim(filename), form='formatted', &
522 & status='old', iostat=io_err, iomsg=io_errmsg)
523 IF (founderror(io_err, noerror, __line__, myfile)) THEN
524 exit_flag=5
525 IF (master) WRITE(stdout,40) trim(filename), trim(io_errmsg)
526 RETURN
527 END IF
528 END IF
529!
530!-----------------------------------------------------------------------
531! Load metadata information from YAML structures.
532!-----------------------------------------------------------------------
533!
534 IF (isyaml) THEN
535 IF (.not.allocated(s)) allocate ( s(nentries) )
536!
537 DO i=1,nentries
538 s(i)%debug_write = ylogical1(i)
539 s(i)%add_offset = yreal1(i)
540 s(i)%scale = yreal2(i)
541!
542 IF (founderror(assign_string(s(i)%standard_name, &
543 & ystring1(i)%value), &
544 & noerror, __line__, myfile)) RETURN
545!
546 IF (founderror(assign_string(s(i)%long_name, &
547 & ystring2(i)%value), &
548 & noerror, __line__, myfile)) RETURN
549!
550 IF (founderror(assign_string(s(i)%short_name, &
551 & ystring3(i)%value), &
552 & noerror, __line__, myfile)) RETURN
553!
554 IF (founderror(assign_string(s(i)%data_netcdf_vname, &
555 & ystring4(i)%vector(1)%value), &
556 & noerror, __line__, myfile)) RETURN
557!
558 IF (founderror(assign_string(s(i)%data_netcdf_tname, &
559 & ystring4(i)%vector(2)%value), &
560 & noerror, __line__, myfile)) RETURN
561!
562 IF (founderror(assign_string(s(i)%source_units, &
563 & ystring5(i)%value), &
564 & noerror, __line__, myfile)) RETURN
565!
566 IF (founderror(assign_string(s(i)%destination_units, &
567 & ystring6(i)%value), &
568 & noerror, __line__, myfile)) RETURN
569!
570 IF (founderror(assign_string(s(i)%source_grid, &
571 & ystring7(i)%value), &
572 & noerror, __line__, myfile)) RETURN
573!
574 IF (founderror(assign_string(s(i)%destination_grid, &
575 & ystring8(i)%value), &
576 & noerror, __line__, myfile)) RETURN
577!
578 IF (founderror(assign_string(s(i)%connected_to, &
579 & ystring9(i)%value), &
580 & noerror, __line__, myfile)) RETURN
581 IF (lowercase(s(i)%connected_to).eq.'false') THEN
582 s(i)%connected=.false.
583 ELSE
584 s(i)%connected=.true.
585 END IF
586!
587 IF (founderror(assign_string(s(i)%regrid_method, &
588 & ystring10(i)%value), &
589 & noerror, __line__, myfile)) RETURN
590!
591 IF (founderror(assign_string(s(i)%extrapolate_method, &
592 & ystring11(i)%value), &
593 & noerror, __line__, myfile)) RETURN
594 END DO
595!
596! Deallocate generic structures.
597!
598 CALL yml%destroy ()
599 IF (allocated(ystring1 )) deallocate (ystring1 )
600 IF (allocated(ystring2 )) deallocate (ystring2 )
601 IF (allocated(ystring3 )) deallocate (ystring3 )
602 IF (allocated(ystring4 )) deallocate (ystring4 )
603 IF (allocated(ystring5 )) deallocate (ystring5 )
604 IF (allocated(ystring6 )) deallocate (ystring6 )
605 IF (allocated(ystring7 )) deallocate (ystring7 )
606 IF (allocated(ystring8 )) deallocate (ystring8 )
607 IF (allocated(ystring9 )) deallocate (ystring9 )
608 IF (allocated(ystring10)) deallocate (ystring10)
609 IF (allocated(ystring11)) deallocate (ystring11)
610 IF (allocated(ylogical1)) deallocate (ylogical1)
611 IF (allocated(yreal1)) deallocate (yreal1)
612 IF (allocated(yreal2)) deallocate (yreal2)
613!
614!-----------------------------------------------------------------------
615! Read in '*.dat' file and load metadata entries into output structure.
616!-----------------------------------------------------------------------
617!
618 ELSE
619!
620! Inquire number of valid entries in metadata file.
621!
622 ientry=0
623 DO WHILE (.true.)
624 READ (iunit,*,err=20,END=10) Cinfo( 1)
625 lvar=len_trim(cinfo(1))
626 IF ((lvar.gt.0).and.(cinfo(1)(1:1).ne.char(33))) THEN
627 ientry=ientry+1
628 READ (iunit,*,err=20,END=10) Cinfo( 2)
629 READ (iunit,*,err=20,END=10) Cinfo( 3)
630 READ (iunit,*,err=20,END=10) Cinfo( 4)
631 READ (iunit,*,err=20,END=10) Cinfo( 5)
632 READ (iunit,*,err=20,END=10) Cinfo( 6)
633 READ (iunit,*,err=20,END=10) Cinfo( 7)
634 READ (iunit,*,err=20,END=10) Cinfo( 8)
635 READ (iunit,*,err=20,END=10) Cinfo( 9)
636 READ (iunit,*,err=20,END=10) Cinfo(10)
637 READ (iunit,*,err=20,END=10) Cinfo(11)
638 READ (iunit,*,err=20,END=10) Cinfo(12)
639 READ (iunit,*,err=20,END=10) connected
640 READ (iunit,*,err=20,END=10) debug_write
641 READ (iunit,*,err=20,END=10) add_offset
642 READ (iunit,*,err=20,END=10) scale
643 END IF
644 END DO
645 10 CONTINUE
646!
647! Allocate ouput structure.
648!
650 IF (.not.allocated(s)) allocate ( s(nentries) )
651!
652! Rewind input unit, reread metadata information.
653!
654 rewind(iunit)
655!
656 ientry=0
657 DO WHILE (ientry.lt.nentries)
658 READ (iunit,*,err=20) cinfo( 1) ! short_name
659 lvar=len_trim(cinfo(1))
660 IF ((lvar.gt.0).and. &
661 (cinfo(1)(1:1).ne.char(33))) THEN
662 READ (iunit,*,err=20) cinfo( 2) ! standard_name
663 READ (iunit,*,err=20) cinfo( 3) ! long_name
664 READ (iunit,*,err=20) cinfo( 4), smodel ! connected_to
665 READ (iunit,*,err=20) cinfo( 5) ! source_units
666 READ (iunit,*,err=20) cinfo( 6) ! source_grid
667 READ (iunit,*,err=20) cinfo( 7) ! data_short_name
668 READ (iunit,*,err=20) cinfo( 8) ! destination_units
669 READ (iunit,*,err=20) cinfo( 9) ! destination_grid
670 READ (iunit,*,err=20) cinfo(10), tname ! data_variables
671 READ (iunit,*,err=20) cinfo(11) ! regrid_method
672 READ (iunit,*,err=20) cinfo(12) ! extrapolate_method
673 READ (iunit,*,err=20) connected
674 READ (iunit,*,err=20) debug_write
675 READ (iunit,*,err=20) add_offset
676 READ (iunit,*,err=20) scale
677 ientry=ientry+1
678!
679! Load metadata into output structure.
680!
681 s(ientry)%connected = connected
682 s(ientry)%debug_write = debug_write
683 s(ientry)%add_offset = add_offset
684 s(ientry)%scale = scale
685!
686 IF (founderror(assign_string(s(ientry)%short_name, &
687 & trim(adjustl(cinfo(1)))), &
688 & noerror, __line__, myfile)) RETURN
689!
690 IF (founderror(assign_string(s(ientry)%standard_name, &
691 & trim(adjustl(cinfo(2)))), &
692 & noerror, __line__, myfile)) RETURN
693!
694 IF (founderror(assign_string(s(ientry)%long_name, &
695 & trim(adjustl(cinfo(3)))), &
696 & noerror, __line__, myfile)) RETURN
697!
698 IF (founderror(assign_string(s(ientry)%connected_to, &
699 & trim(adjustl(smodel))), &
700 & noerror, __line__, myfile)) RETURN
701!
702 IF (founderror(assign_string(s(ientry)%source_units, &
703 & trim(adjustl(cinfo(5)))), &
704 & noerror, __line__, myfile)) RETURN
705!
706 IF (founderror(assign_string(s(ientry)%source_grid, &
707 & trim(adjustl(cinfo(6)))), &
708 & noerror, __line__, myfile)) RETURN
709!
710 IF (founderror(assign_string(s(ientry)%destination_units, &
711 & trim(adjustl(cinfo(8)))), &
712 & noerror, __line__, myfile)) RETURN
713!
714 IF (founderror(assign_string(s(ientry)%destination_grid, &
715 & trim(adjustl(cinfo(9)))), &
716 & noerror, __line__, myfile)) RETURN
717!
718 IF (founderror(assign_string(s(ientry)%data_netcdf_vname, &
719 & trim(adjustl(cinfo(10)))), &
720 & noerror, __line__, myfile)) RETURN
721!
722 IF (founderror(assign_string(s(ientry)%data_netcdf_tname, &
723 & trim(adjustl(tname))), &
724 & noerror, __line__, myfile)) RETURN
725!
726 IF (founderror(assign_string(s(ientry)%regrid_method, &
727 & trim(adjustl(cinfo(11)))), &
728 & noerror, __line__, myfile)) RETURN
729!
730 IF (founderror(assign_string(s(ientry)%extrapolate_method, &
731 & trim(adjustl(cinfo(12)))), &
732 & noerror, __line__, myfile)) RETURN
733 END IF
734 END DO
735 CLOSE (iunit)
736 END IF
737!
738! Report.
739!
740 IF (master.and.ldebugmetadata) THEN
741 WRITE (stdout,'(/,2a,/,a)') &
742 & 'Coupling Metadata Dictionary, File: ', &
743 & trim(filename), repeat('=',28)
744 DO i=1,SIZE(s)
745 WRITE (stdout,'(/,a,a)') ' - standard_name: ', &
746 & trim(s(i)%standard_name)
747 WRITE (stdout,'(a,a)') ' long_name: ', &
748 & trim(s(i)%long_name)
749 WRITE (stdout,'(a,a)') ' short_name: ', &
750 & trim(s(i)%short_name)
751 WRITE (stdout,'(a,a)') ' data_netcdf_variable: ', &
752 & trim(s(i)%data_netcdf_vname)
753 WRITE (stdout,'(a,a)') ' data_netcdf_time: ', &
754 & trim(s(i)%data_netcdf_tname)
755 WRITE (stdout,'(a,a)') ' source_units: ', &
756 & trim(s(i)%source_units)
757 WRITE (stdout,'(a,a)') ' destination_units: ', &
758 & trim(s(i)%destination_units)
759 WRITE (stdout,'(a,a)') ' source_grid: ', &
760 & trim(s(i)%source_grid)
761 WRITE (stdout,'(a,a)') ' destination_grid: ', &
762 & trim(s(i)%destination_grid)
763 WRITE (stdout,'(a,1p,e15.8)') ' add_offset: ', &
764 & s(i)%add_offset
765 WRITE (stdout,'(a,1p,e15.8)') ' scale: ', &
766 & s(i)%scale
767 WRITE (stdout,'(a,l1)') ' debug_write: ', &
768 & s(i)%debug_write
769 WRITE (stdout,'(a,l1)') ' connected: ', &
770 & s(i)%connected
771 WRITE (stdout,'(a,a)') ' connected_to: ', &
772 & trim(s(i)%connected_to)
773 WRITE (stdout,'(a,a)') ' regrid_method: ', &
774 & trim(s(i)%regrid_method)
775 WRITE (stdout,'(a,a)') ' extrapolate_method: ', &
776 & trim(s(i)%extrapolate_method)
777 END DO
778 FLUSH (stdout)
779 END IF
780!
781 RETURN
782 20 IF (master) WRITE (stdout,50) trim(adjustl(cinfo(1))), &
783 & trim(filename)
784!
785 30 FORMAT (/,' COUPLING_METADATA - Unable to create YAML object', &
786 & ' for ROMS I/O metadata file: ',/,21x,a,/, &
787 & 21x,'Default file is located in source directory.')
788 40 FORMAT (/,' COUPLING_METADATA - Unable to open ROMS coupling', &
789 & ' coupling file:',/,21x,a,/,21x,'ERROR: ',a,/, &
790 & 21x,'Default file is located in source directory.')
791 50 FORMAT (/,' COUPLING_METADATA - Error while reading information', &
792 & 'for metadata variable: ',a,/,21x,'File: ',a)
793!
794 END SUBROUTINE coupling_metadata
795!
796 FUNCTION io_metadata (FirstPass, Vinfo, scale, offset) &
797 result(ldone)
798!
799!=======================================================================
800! !
801! It processes ROMS input/output fields metadata entry-by-entry from !
802! 'varinfo.dat' or 'varinfo.yaml' dictionary. !
803! !
804! On Output: !
805! !
806! FirsPass Switch to initialize metadata processing (logical) !
807! !
808! Vinfo I/O Variable information (string array) !
809! Vinfo(1): Field variable short-name !
810! Vinfo(2): Long-name attribute !
811! Vinfo(3): Units attribute !
812! Vinfo(4): Field attribute !
813! Vinfo(5): Associated time variable name !
814! Vinfo(6): Standard-name attribute !
815! Vinfo(7): Staggered C-grid variable type: !
816! 'nulvar' => non-grided variable !
817! 'p2dvar' => 2D PHI-variable !
818! 'r2dvar' => 2D RHO-variable !
819! 'u2dvar' => 2D U-variable !
820! 'v2dvar' => 2D V-variable !
821! 'p3dvar' => 3D PSI-variable !
822! 'r3dvar' => 3D RHO-variable !
823! 'u3dvar' => 3D U-variable !
824! 'v3dvar' => 3D V-variable !
825! 'w3dvar' => 3D W-variable !
826! 'b3dvar' => 3D BED-sediment !
827! 'l3dvar' => 3D spectral light variable !
828! 'l4dvar' => 4D spectral light variable !
829! Vinfo(8): Index code for information arrays !
830! !
831! scale Scale to convert input data to model units (real) !
832! !
833! offeset Value to add to input data (real) !
834! !
835! Ldone True if end-of-file or dictionary found !
836! !
837!=======================================================================
838!
839! Imported variable declarations.
840!
841 logical, intent(inout) :: firstpass
842!
843 real(dp), intent(out) :: offset, scale
844!
845 character (len=*), intent(out) :: vinfo(:)
846!
847! Local variable declarations.
848!
849 logical, save :: isdat = .false.
850 logical, save :: isyaml = .false.
851 logical :: ldone
852!
853 integer, parameter :: iunit = 10
854 integer :: idot, lstr, lvar
855 integer :: i, j, io_err
856!
857 character (len=256) :: io_errmsg
858
859 character (len=*), parameter :: myfile = &
860 & __FILE__//", io_metadata"
861!
862!-----------------------------------------------------------------------
863! On first pass, initialize metadata processing.
864!-----------------------------------------------------------------------
865!
866! Initialize.
867!
868 ldone=.false.
869!
870! Determine metadata file extension: 'varinfo.dat' or
871! 'varinfo.yaml'
872!
873 IF (firstpass) THEN
874 firstpass=.false.
875!
876 lstr=len_trim(varname)
877 idot=index(varname(1:lstr), char(46), back=.true.)
878 SELECT CASE (lowercase(varname(idot+1:lstr)))
879 CASE ('dat')
880 isdat=.true.
881 CASE ('yaml', 'yml')
882 isyaml=.true.
883 END SELECT
884!
885! If YAML metadata, create dictionary and extract values.
886!
887 IF (isyaml) THEN
888 ientry=0
889!
890 IF (founderror(yaml_initialize(yml, trim(varname), &
891 & lreportyaml), &
892 & noerror, __line__, myfile)) THEN
893 ldone=.true.
894 IF (master) WRITE (stdout,30) trim(varname)
895 RETURN
896 END IF
897!
898 IF (founderror(yaml_get(yml, 'metadata.variable', &
899 & ystring1), &
900 & noerror, __line__, myfile)) RETURN
901 nentries=SIZE(ystring1, dim=1)
902!
903 IF (founderror(yaml_get(yml, 'metadata.long_name', &
904 & ystring2), &
905 & noerror, __line__, myfile)) RETURN
906!
907 IF (founderror(yaml_get(yml, 'metadata.units', &
908 & ystring3), &
909 & noerror, __line__, myfile)) RETURN
910!
911 IF (founderror(yaml_get(yml, 'metadata.field', &
912 & ystring4), &
913 & noerror, __line__, myfile)) RETURN
914!
915 IF (founderror(yaml_get(yml, 'metadata.time', &
916 & ystring5), &
917 & noerror, __line__, myfile)) RETURN
918!
919 IF (founderror(yaml_get(yml, 'metadata.standard_name', &
920 & ystring6), &
921 & noerror, __line__, myfile)) RETURN
922!
923 IF (founderror(yaml_get(yml, 'metadata.type', &
924 & ystring7), &
925 & noerror, __line__, myfile)) RETURN
926!
927 IF (founderror(yaml_get(yml, 'metadata.index_code', &
928 & ystring8), &
929 & noerror, __line__, myfile)) RETURN
930!
931 IF (allocated(yreal1)) deallocate (yreal1)
932 allocate ( yreal1(nentries) )
933 IF (founderror(yaml_get(yml, 'metadata.add_offset', &
934 & yreal1), &
935 & noerror, __line__, myfile)) RETURN
936!
937 IF (allocated(yreal2)) deallocate (yreal2)
938 allocate ( yreal2(nentries) )
939 IF (founderror(yaml_get(yml, 'metadata.scale', &
940 & yreal2), &
941 & noerror, __line__, myfile)) RETURN
942!
943! Otherwise, open deprecated 'varinfo.dat' file.
944!
945 ELSE IF (isdat) THEN
946 OPEN (unit=iunit, file=trim(varname), form='formatted', &
947 & status='old', iostat=io_err, iomsg=io_errmsg)
948 IF (founderror(io_err, noerror, __line__, myfile)) THEN
949 exit_flag=5
950 ldone=.true.
951 IF (master) WRITE(stdout,40) trim(varname), trim(io_errmsg)
952 RETURN
953 END IF
954 END IF
955 END IF
956!
957!-----------------------------------------------------------------------
958! Process metadata entries.
959!-----------------------------------------------------------------------
960!
961 DO j=1,SIZE(vinfo)
962 DO i=1,len(vinfo(1))
963 vinfo(j)(i:i)=char(32)
964 END DO
965 END DO
966!
967! Extract metadata information from YAML structures.
968!
969 IF (isyaml) THEN
970 ientry=ientry+1 ! advance variable counter
971 IF (ientry.le.nentries) THEN
972 vinfo(1)=ystring1(ientry)%value ! 'variable' key
973 vinfo(2)=ystring2(ientry)%value ! 'long_name' key
974 vinfo(3)=ystring3(ientry)%value ! 'units' key
975 vinfo(4)=ystring4(ientry)%value ! 'field' key
976 vinfo(5)=ystring5(ientry)%value ! 'time' key
977 vinfo(6)=ystring6(ientry)%value ! 'standard_name' key
978 vinfo(7)=ystring7(ientry)%value ! 'type' key
979 vinfo(8)=ystring8(ientry)%value ! 'index_code' key
980 offset =yreal1(ientry) ! 'add_offset' key
981 scale =yreal2(ientry) ! 'scale' key
982 ELSE
983 ldone=.true.
984 CALL yml%destroy ()
985 IF (allocated(ystring1)) deallocate (ystring1)
986 IF (allocated(ystring2)) deallocate (ystring2)
987 IF (allocated(ystring3)) deallocate (ystring3)
988 IF (allocated(ystring4)) deallocate (ystring4)
989 IF (allocated(ystring5)) deallocate (ystring5)
990 IF (allocated(ystring6)) deallocate (ystring6)
991 IF (allocated(ystring7)) deallocate (ystring7)
992 IF (allocated(ystring8)) deallocate (ystring8)
993 IF (allocated(yreal1)) deallocate (yreal1)
994 IF (allocated(yreal2)) deallocate (yreal2)
995 RETURN
996 END IF
997!
998! Otherwise, read in next metadata entry. The 'standard_name' and
999! 'add_offset' attributes are unavailable in 'varinfo.dat'.
1000!
1001 ELSE IF (isdat) THEN
1002 DO WHILE (.true.)
1003 READ (iunit,*,err=10,END=20) Vinfo(1) ! variable
1004 lvar=len_trim(vinfo(1))
1005 IF ((lvar.gt.0).and.(vinfo(1)(1:1).ne.char(33)).and. &
1006 & (vinfo(1)(1:1).ne.char(36))) THEN
1007 READ (iunit,*,err=10) vinfo(2) ! long_name
1008 READ (iunit,*,err=10) vinfo(3) ! units
1009 READ (iunit,*,err=10) vinfo(4) ! field
1010 READ (iunit,*,err=10) vinfo(5) ! associated time
1011 vinfo(6)='nulvar' ! standard_name
1012 READ (iunit,*,err=10) vinfo(8) ! index code
1013 READ (iunit,*,err=10) vinfo(7) ! C-grid type
1014 READ (iunit,*,err=10) scale
1015 offset =0.0_dp ! add_offset
1016 ldone=.false.
1017 RETURN
1018 END IF
1019 END DO
1020 10 WRITE (stdout,50) trim(adjustl(vinfo(1)))
1021 stop
1022 20 CLOSE (iunit)
1023 ldone=.true.
1024 END IF
1025!
1026 30 FORMAT (/,' IO_METADATA - Unable to create YAML object for', &
1027 & ' ROMS I/O metadata file: ',/,15x,a,/, &
1028 & 15x,'Default file is located in source directory.')
1029 40 FORMAT (/,' IO_METADATA - Unable to open ROMS I/O metadata ', &
1030 & 'file:',/,15x,a,/,15x,'ERROR: ',a,/, &
1031 & 15x,'Default file is located in source directory.')
1032 50 FORMAT (/,' IO_METADATA - Error while reading information for ', &
1033 & 'variable: ',a)
1034!
1035 RETURN
1036 END FUNCTION io_metadata
1037!
1038 FUNCTION metadata_has (S, short_name) RESULT (Findex)
1039!
1040!=======================================================================
1041! !
1042! It scans the fields metadata object (TYPE CouplingField) and !
1043! returns the index location in the block list of the requested !
1044! short-name keyword. !
1045! !
1046! On Input: !
1047! !
1048! S Fields metadata object (TYPE CouplingField) !
1049! !
1050! short_name Field short_name to find (string) !
1051! !
1052! On Output: !
1053! !
1054! Findex Index location in fields metadata list (integer) !
1055! !
1056!=======================================================================
1057!
1058! Imported variable declarations.
1059!
1060 TYPE (couplingfield), allocatable, intent(in) :: s(:)
1061 character (len=*), intent(in) :: short_name
1062!
1063! Local variable declarations.
1064!
1065 integer :: findex
1066 integer :: i
1067!
1068!-----------------------------------------------------------------------
1069! Find index of specified field from names list.
1070!-----------------------------------------------------------------------
1071!
1072 findex=-1
1073!
1074 DO i=1,SIZE(s)
1075 IF (s(i)%short_name.eq.short_name) THEN
1076 findex=i
1077 EXIT
1078 END IF
1079 END DO
1080!
1081 RETURN
1082 END FUNCTION metadata_has
1083!
1084 END MODULE get_metadata_mod
subroutine, public coupling_metadata(filename, s)
type(yaml_tree) yml
type(yaml_svec), dimension(:), allocatable ystring11
logical ldebugmetadata
type(yaml_svec), dimension(:), allocatable ystring2
type(yaml_svec), dimension(:), allocatable ystring7
subroutine, public cmeps_metadata(self, filename, key, s)
type(yaml_svec), dimension(:), allocatable ystring12
logical function, public io_metadata(firstpass, vinfo, scale, offset)
real(dp), dimension(:), allocatable yreal2
integer function, public metadata_has(s, short_name)
type(yaml_svec), dimension(:), allocatable ystring9
type(yaml_svec), dimension(:), allocatable ystring6
type(yaml_svec), dimension(:), allocatable ystring8
type(yaml_svec), dimension(:), allocatable ystring5
type(yaml_svec), dimension(:), allocatable ystring10
logical, dimension(:), allocatable ylogical1
type(yaml_svec), dimension(:), allocatable ystring3
type(yaml_svec), dimension(:), allocatable ystring4
real(dp), dimension(:), allocatable yreal1
type(yaml_svec), dimension(:), allocatable ystring1
type(t_io), dimension(:), allocatable err
integer stdout
character(len=256) varname
integer, parameter dp
Definition mod_kinds.F:25
logical master
integer exit_flag
integer noerror
character(len(sinp)) function, public lowercase(sinp)
Definition strings.F:531
integer function, public assign_string(a, string)
Definition strings.F:368
logical function, public founderror(flag, noerr, line, routine)
Definition strings.F:52
integer function, public yaml_initialize(self, filename, report)
integer, parameter iunit