SOCA
soca_fields_metadata_mod.F90
Go to the documentation of this file.
1 ! (C) Copyright 2021-2021 UCAR
2 !
3 ! This software is licensed under the terms of the Apache Licence Version 2.0
4 ! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
5 
6 !> Metadata for soca_fields
8 
9 use fckit_configuration_module, only: fckit_configuration, fckit_yamlconfiguration
10 use fckit_pathname_module, only : fckit_pathname
11 
12 implicit none
13 private
14 
15 ! ------------------------------------------------------------------------------
16 !> Holds all of the user configurable meta data associated with a single field
17 !!
18 !! Instances of these types are to be held by soca_fields_metadata
19 type, public :: soca_field_metadata
20  character(len=:), allocatable :: name !< internal name used only by soca code
21  character(len=1) :: grid !< "h", "u" or "v"
22  logical :: masked !< should use land mask when interpolating
23  character(len=:), allocatable :: levels !< "1", or "full_ocn"
24  character(len=:), allocatable :: getval_name !< variable name used by UFO
25  character(len=:), allocatable :: getval_name_surface ! name used by UFO for the suface (if this is a 3D field)
26  character(len=:), allocatable :: io_file !< the restart file domain (ocn, sfc, ice)
27  character(len=:), allocatable :: io_name !< the name use in the restart IO
28  character(len=:), allocatable :: property !< physical property of the field, "none" or "positive_definite"
29  logical :: dummy_atm !< a meaningless dummy field, for the CRTM hacks
30 end type
31 
32 
33 ! ------------------------------------------------------------------------------
34 !> A collection of soca_field_metadata types representing ALL possible fields
35 !! (state, increment, other derived) in soca. These are read in from a configuration file.
36 type, public :: soca_fields_metadata
37 
38  type(soca_field_metadata), private, allocatable :: metadata(:)
39 
40 contains
41 
42  !> \copybrief soca_fields_metadata_create \see soca_fields_metadata_create
43  procedure :: create => soca_fields_metadata_create
44 
45  !> \copybrief soca_fields_metadata_clone \see soca_fields_metadata_clone
46  procedure :: clone => soca_fields_metadata_clone
47 
48  !> \copybrief soca_fields_metadata_get \see soca_fields_metadata_get
49  procedure :: get => soca_fields_metadata_get
50 end type
51 
52 
53 ! ------------------------------------------------------------------------------
54 
55 contains
56 
57 ! ------------------------------------------------------------------------------
58 
59 !> Create the main soca_fields_metadata instance by reading in parameters from a
60 !! yaml file.
61 !!
62 !! See the members of soca_field_metadata for a list of valid options
63 !!
64 !! \throws abor1_ftn aborts if there are duplicate fields
65 !! \relates soca_fields_metadata_mod::soca_fields_metadata
66 subroutine soca_fields_metadata_create(self, filename)
67  class(soca_fields_metadata), intent(inout) :: self
68  character(len=:), allocatable, intent(in) :: filename !< filename of the yaml configuration
69 
70  type(fckit_configuration) :: conf
71  type(fckit_configuration), allocatable :: conf_list(:)
72 
73  integer :: i, j
74  logical :: bool
75  character(len=:), allocatable :: str
76 
77  ! parse all the metadata from a yaml configuration file
78  conf = fckit_yamlconfiguration( fckit_pathname(filename))
79  call conf%get_or_die("", conf_list)
80  allocate(self%metadata(size(conf_list)))
81  do i=1,size(self%metadata)
82 
83  call conf_list(i)%get_or_die("name", self%metadata(i)%name)
84 
85  if(.not. conf_list(i)%get("grid", str)) str = 'h'
86  self%metadata(i)%grid = str
87 
88  if(.not. conf_list(i)%get("masked", bool)) bool = .true.
89  self%metadata(i)%masked = bool
90 
91  if(.not. conf_list(i)%get("levels", str)) str = "1"
92  self%metadata(i)%levels = str
93 
94  if(.not. conf_list(i)%get("getval name", str)) str=self%metadata(i)%name
95  self%metadata(i)%getval_name = str
96 
97  if(.not. conf_list(i)%get("getval name surface", str)) str=""
98  self%metadata(i)%getval_name_surface = str
99 
100  if(.not. conf_list(i)%get("io name", str)) str = ""
101  self%metadata(i)%io_name = str
102 
103  if(.not. conf_list(i)%get("io file", str)) str = ""
104  self%metadata(i)%io_file = str
105 
106  if(.not. conf_list(i)%get("property", str)) str = "none"
107  self%metadata(i)%property = str
108 
109  if(.not. conf_list(i)%get("dummy_atm", bool)) bool = .false.
110  self%metadata(i)%dummy_atm = bool
111  end do
112 
113  ! check for duplicates
114  do i=1,size(self%metadata)
115  do j=i+1,size(self%metadata)
116  if ( self%metadata(i)%name == self%metadata(j)%name .or. &
117  self%metadata(i)%name == self%metadata(j)%getval_name .or. &
118  self%metadata(i)%name == self%metadata(j)%getval_name_surface .or. &
119  self%metadata(i)%getval_name == self%metadata(j)%name .or. &
120  self%metadata(i)%getval_name == self%metadata(j)%getval_name .or. &
121  self%metadata(i)%getval_name == self%metadata(j)%getval_name_surface .or. &
122  ( self%metadata(i)%getval_name_surface /= "" .and. ( &
123  self%metadata(i)%getval_name_surface == self%metadata(j)%name .or. &
124  self%metadata(i)%getval_name_surface == self%metadata(j)%getval_name ))) then
125  str=repeat(" ",1024)
126  write(str, *) "Duplicate field metadata: ", i, self%metadata(i)%name, &
127  j, self%metadata(j)%name
128  call abor1_ftn(str)
129  end if
130  end do
131  end do
132 
133 end subroutine
134 
135 
136 ! ------------------------------------------------------------------------------
137 !> Make a copy from \rhs to \p self
138 !!
139 !! \relates soca_fields_metadata_mod::soca_fields_metadata
140 subroutine soca_fields_metadata_clone(self, rhs)
141  class(soca_fields_metadata), intent(inout) :: self
142  class(soca_fields_metadata), intent(in) :: rhs !< metadata to clone \b from
143 
144  self%metadata = rhs%metadata
145 
146 end subroutine
147 
148 
149 ! ------------------------------------------------------------------------------
150 !> Get the metadata for the field with the given name
151 !!
152 !! The \p name can match any of \c name, \c getval_name, or \c getval_name_surface
153 function soca_fields_metadata_get(self, name) result(field)
154  class(soca_fields_metadata), intent(in) :: self
155  character(len=:), allocatable, intent(in) :: name !< the name to search for
156  type(soca_field_metadata) :: field
157 
158  integer :: i
159 
160  ! find the field by any of its internal or getval names
161  do i=1,size(self%metadata)
162  if( trim(self%metadata(i)%name) == trim(name) .or. &
163  trim(self%metadata(i)%getval_name) == trim(name) .or. &
164  trim(self%metadata(i)%getval_name_surface) == trim(name) ) then
165  field = self%metadata(i)
166  return
167  endif
168  enddo
169 
170  call abor1_ftn("Unable to find field metadata for: " // name)
171 
172 end function
173 
174 
175 end module
Metadata for soca_fields.
type(soca_field_metadata) function soca_fields_metadata_get(self, name)
Get the metadata for the field with the given name.
Holds all of the user configurable meta data associated with a single field.
A collection of soca_field_metadata types representing ALL possible fields (state,...