FV3 Bundle
oda_types.F90
Go to the documentation of this file.
1 !***********************************************************************
2 !* GNU Lesser General Public License
3 !*
4 !* This file is part of the GFDL Flexible Modeling System (FMS).
5 !*
6 !* FMS is free software: you can redistribute it and/or modify it under
7 !* the terms of the GNU Lesser General Public License as published by
8 !* the Free Software Foundation, either version 3 of the License, or (at
9 !* your option) any later version.
10 !*
11 !* FMS is distributed in the hope that it will be useful, but WITHOUT
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
13 !* FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
14 !* for more details.
15 !*
16 !* You should have received a copy of the GNU Lesser General Public
17 !* License along with FMS. If not, see <http://www.gnu.org/licenses/>.
18 !***********************************************************************
20 #ifndef MAX_LEVS_FILE_
21 #define MAX_LEVS_FILE_ 50
22 #endif
23 
24 #ifndef MAX_LINKS_
25 #define MAX_LINKS_ 100
26 #endif
27 
28 !============================================================
29 ! This module contains type declarations and default values
30 ! for oda modules.
31 !============================================================
32 
33 ! Contact: Matthew.Harrison@gfdl.noaa.gov
34 
36  use mpp_mod, only : stdout
37  use mpp_domains_mod, only : domain2d
38 
39  implicit none
40 
41  private
42 
43  integer, parameter, public :: max_levels_file = max_levs_file_ !< Controls record length for optimal storage
44  integer, parameter, public :: max_neighbors = 100 !< Maximum number of neighbors for QC or analysis for profiles
45  integer, parameter, public :: max_links = max_links_ !< Maximum number of records per profile for storage for profiles
46 
47  ! Additional Pramaeters needed for snz's ECDA
48  integer, parameter, public :: drop_profiler = 10
49  integer, parameter, public :: mooring = 20
50  integer, parameter, public :: satellite = 30
51  integer, parameter, public :: drifter = 40
52  integer, parameter, public :: ship = 50
53  integer, parameter, public :: unknown = 0
54  integer, parameter, public :: tao = 1 !< moorings
55  integer, parameter, public :: pirata = 2 !< moorings
56  integer, parameter, public :: xbt = 1 !< station measurements
57  integer, parameter, public :: ctd = 2 !< station measurements
58  integer, parameter, public :: mbt = 3 !< station measurements
59  integer, parameter, public :: argo = 1
60 
61  ! Codes for modeling error disttributions
62  integer, parameter, public :: cossq_lat = 10
63 
64  integer, save, public :: temp_id = 1
65  integer, save, public :: salt_id = 2
66 
67  ! List of variables for ODA
68 #ifndef ENABLE_ECDA
69  real, parameter, public :: missing_value = -1.e20
70 #else
71  !::sdu:: ECDA oda files need this value to different
72  real, parameter, public :: missing_value = -1.e10
73 #endif
74 
75  type, public :: forward_model_type
76  real, dimension(:,:,:,:), pointer :: wgt ! interpolation weights
77  end type forward_model_type
78 
79  type, public :: ocean_profile_type
80  integer :: variable !< variable ids are defined by the ocean_types module (e.g. TEMP_ID, SALT_ID)
81  integer :: inst_type !< instrument types are defined by platform class (e.g. MOORING, DROP, etc.) and instrument type (XBT, CDT, etc.)
82  integer :: nvar
83  real :: project ! e.g. FGGE, COARE, ACCE, ...
84  real :: probe ! MBT, XBT, drifting buoy
85  real :: ref_inst ! instrument (thermograph, hull sensor, ...)
86  integer :: wod_cast_num
87  real :: fix_depth
88  real :: ocn_vehicle
89  real :: database_id
90  integer :: levels
91  integer :: profile_flag ! an overall flag for the profile
92  integer :: profile_flag_s ! an overall flag for the profile salinity
93  real :: lat, lon
94  logical :: accepted
95  integer :: nlinks
96  type(ocean_profile_type), pointer, dimension(:) :: next ! Large profiles are stored as linked list.
97  integer, dimension(MAX_NEIGHBORS) :: nbr_index
98  real, dimension(MAX_NEIGHBORS) :: nbr_dist ! distance in radians
99  real, dimension(:), pointer :: depth, data_t, data_s
100  real, dimension(:), pointer :: data
101  integer, dimension(:), pointer :: flag_t
102  integer, dimension(:), pointer :: flag_s ! level-by-level flags for salinity
103  logical, dimension(:), pointer :: flag
104  real :: temp_err, salt_err ! measurement error
105  real, dimension(:), pointer :: ms_t ! ms temperature by level
106  real, dimension(:), pointer :: ms_s ! ms salinity by level
107  real, dimension(:), pointer :: ms_inv
108  real, dimension(:), pointer :: ms
109  type(time_type) :: time
110  integer :: yyyy
111  integer :: mmdd
112  type(time_type), pointer :: model_time ! each profile can be associated with a first-guess field with an associated time and grid
113  type(grid_type), pointer :: model_grid
114  real :: i_index, j_index ! model longitude and latitude indices respectively
115  real, dimension(:), pointer :: k_index ! model depth indices
116  type(forward_model_type) :: forward_model ! linear operation from model to observation
117  type(time_type) :: tdiff ! positive difference between model time and observation time
118  end type ocean_profile_type
119 
120  type, public :: ocean_surface_type
121  integer :: variable ! variable ids are defined by the ocean_types module (e.g. TEMP_ID, SALT_ID, ...)
122  integer :: inst_type ! instrument types are defined by platform class (e.g. MOORING, DROP) and instrument type (XBT, CTD, ...)
123  integer :: qc_flag, nobs
124  logical :: is_gridded
125  integer :: nlon, nlat
126  real, pointer, dimension(:) :: lat=>null(), lon=>null()
127  logical :: accepted
128  real, pointer, dimension(:) :: data => null()
129  real, dimension(:), pointer :: ms_inv => null()
130  real, dimension(:), pointer :: ms => null()
131  real, dimension(:), pointer :: i_index=>null(), j_index=>null() ! model indices
132  real, pointer, dimension(:,:) :: data2 => null()
133  real, dimension(:,:), pointer :: ms2 => null()
134  real, dimension(:,:), pointer :: i_index2=>null(), j_index2=>null() ! model indices
135  real :: k_index
136  type(forward_model_type) :: forward_model
137  type(time_type) :: time
138  integer :: yyyy
139  integer :: mmdd
140  character(len=8) :: wmo_id
141  type(time_type), pointer :: model_time => null()
142  type(grid_type), pointer :: model_grid => null()
143  ! positive difference between current model time
144  ! and observation time
145  type(time_type) :: tdiff
146  end type ocean_surface_type
147 
148  type, public :: da_flux_type
149  real, pointer, dimension(:,:) :: u_flux => null()
150  real, pointer, dimension(:,:) :: v_flux => null()
151  real, pointer, dimension(:,:) :: t_flux => null()
152  real, pointer, dimension(:,:) :: q_flux => null()
153  real, pointer, dimension(:,:) :: salt_flux => null()
154  real, pointer, dimension(:,:) :: lw_flux => null()
155  real, pointer, dimension(:,:) :: sw_flux_vis_dir => null()
156  real, pointer, dimension(:,:) :: sw_flux_vis_dif => null()
157  real, pointer, dimension(:,:) :: sw_flux_nir_dir => null()
158  real, pointer, dimension(:,:) :: sw_flux_nir_dif => null()
159  end type da_flux_type
160 
161  type, public :: ocn_obs_flag_type
162  logical :: use_prf_as_obs
163  logical :: use_ssh_as_obs
164  logical :: use_sst_as_obs
165  logical :: use_suv_as_obs
166  logical :: use_woa05_t
167  logical :: use_woa05_s
168  end type ocn_obs_flag_type
169 
170  type, public :: grid_type
171  real, pointer, dimension(:,:) :: x=>null(), y=>null()
172  real, pointer, dimension(:,:) :: x_bound=>null(), y_bound=>null()
173  real, pointer, dimension(:,:) :: dx=>null(), dy=>null()
174  real, pointer, dimension(:) :: z=>null(), z_bound=>null()
175  real, pointer, dimension(:) :: dz => null()
176  real, pointer, dimension(:,:,:) :: mask
177  type(domain2d), pointer :: dom ! FMS domain type
178  logical :: cyclic
179  integer :: ni, nj, nk
180  end type grid_type
181 
182  type, public :: field_type
183  type(grid_type) :: grid
184  real, pointer, dimension(:,:,:) :: data => null()
185  end type field_type
186 
187 
188  type, public :: field_dist_type_3d
189  integer :: error_model
190  character(len=32) :: name
191  type(grid_type), pointer :: grid => null()
192  real, pointer, dimension(:,:,:) :: ex=>null(), vr=>null()
193  real, pointer, dimension(:,:,:) :: obs_d => null() ! obs minus expected value
194  end type field_dist_type_3d
195 
196  type, public :: field_dist_type_2d
197  integer :: error_model
198  character(len=32) :: name
199  type(grid_type), pointer :: grid => null()
200  real, pointer, dimension(:,:) :: ex=>null(), vr=>null()
201  end type field_dist_type_2d
202 
203  type, public :: ocean_dist_type
204  type(field_dist_type_3d) :: temp,salt,u,v
205  type(field_dist_type_2d) :: eta
206  end type ocean_dist_type
207 
208  type, public :: obs_clim_type
209  real, pointer, dimension(:,:) :: sst_obs
210  end type obs_clim_type
211 
212  public init_obs
213 
214  interface init_obs
215  module procedure init_obs_profile
216  end interface
217 
218  contains
219 
220  subroutine init_obs_profile(profile)
221  type(ocean_profile_type), intent(inout) :: profile
222 
223  profile%nvar = 0
224  profile%project = -1.0
225  profile%probe = -1.0
226  profile%wod_cast_num = -1
227  profile%ref_inst = -1.0
228  profile%fix_depth = -1.0
229  profile%ocn_vehicle = -1.0
230  profile%database_id = -1.0
231  profile%levels = 0
232  profile%profile_flag = 0
233  profile%profile_flag_s = 0
234  profile%lat = -1.e10
235  profile%lon = -1.e10
236  profile%accepted = .true.
237  if (associated(profile%next)) deallocate(profile%next)
238  profile%nlinks = 0
239  profile%nbr_index(:) = -1
240  profile%nbr_dist(:) = -1.0
241  if (associated(profile%depth)) deallocate(profile%depth)
242  if (associated(profile%data_t)) deallocate(profile%data_t)
243  if (associated(profile%data_s)) deallocate(profile%data_s)
244  if (associated(profile%flag_t)) deallocate(profile%flag_t)
245  if (associated(profile%flag_s)) deallocate(profile%flag_s)
246  if (associated(profile%ms_t)) deallocate(profile%ms_t)
247  if (associated(profile%ms_s)) deallocate(profile%ms_s)
248  profile%temp_err = -1.0
249  profile%salt_err = -1.0
250  profile%time = set_time(0,0)
251  profile%yyyy = 0
252  profile%mmdd = 0
253  if (associated(profile%model_time)) deallocate(profile%model_time)
254  if (associated(profile%model_grid)) deallocate(profile%model_grid)
255  profile%i_index = -1
256  profile%j_index = -1
257  if (associated(profile%k_index)) deallocate(profile%k_index)
258  profile%tdiff = set_time(0,0)
259 
260  return
261 
262  end subroutine init_obs_profile
263 
264 end module oda_types_mod
integer, parameter, public satellite
Definition: oda_types.F90:50
integer, parameter, public max_levels_file
Controls record length for optimal storage.
Definition: oda_types.F90:43
integer, parameter, public drifter
Definition: oda_types.F90:51
integer, parameter, public xbt
station measurements
Definition: oda_types.F90:56
integer, parameter, public max_links
Maximum number of records per profile for storage for profiles.
Definition: oda_types.F90:45
integer, parameter, public cossq_lat
Definition: oda_types.F90:62
subroutine init_obs_profile(profile)
Definition: oda_types.F90:221
Definition: mpp.F90:39
integer, save, public salt_id
Definition: oda_types.F90:65
integer, parameter, public max_neighbors
Maximum number of neighbors for QC or analysis for profiles.
Definition: oda_types.F90:44
integer, save, public temp_id
Definition: oda_types.F90:64
integer, parameter, public argo
Definition: oda_types.F90:59
integer, parameter, public ship
Definition: oda_types.F90:52
integer, parameter, public mooring
Definition: oda_types.F90:49
integer, parameter, public unknown
Definition: oda_types.F90:53
real, parameter, public missing_value
Definition: oda_types.F90:69
integer, parameter, public ctd
station measurements
Definition: oda_types.F90:57
integer, parameter, public drop_profiler
Definition: oda_types.F90:48
integer, parameter, public tao
moorings
Definition: oda_types.F90:54
integer, parameter, public mbt
station measurements
Definition: oda_types.F90:58
integer, parameter, public pirata
moorings
Definition: oda_types.F90:55