New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
obs_field.F90 in NEMO/branches/UKMO/NEMO_4.0.4_generic_obs/src/OCE/OBS – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.4_generic_obs/src/OCE/OBS/obs_field.F90 @ 15144

Last change on this file since 15144 was 15144, checked in by dford, 3 years ago

Initial implementation of generic OBS interface.

File size: 23.9 KB
Line 
1MODULE obs_field
2   !!=====================================================================
3   !!                       ***  MODULE obs_field  ***
4   !! Observation diagnostics: Routines specific to model variables
5   !!=====================================================================
6   !! History : 4.0  !  2021-06  (D Ford)  Original code
7   !!----------------------------------------------------------------------
8   !!   obs_group_alloc   : allocate observation group types
9   !!   obs_group_dealloc : deallocate observation group types
10   !!   obs_group_check   : check observation group options
11   !!----------------------------------------------------------------------
12
13   !! * Modules used
14   USE iom                ! In/out manager
15   USE par_kind, ONLY : & ! Precision variables
16      & wp
17   USE obs_oper, ONLY : & ! Max number of daily avgd obs types
18      & imaxavtypes
19   USE obs_surf_def       ! Surface data definitions
20   USE obs_profiles_def   ! Profile data definitions
21
22   IMPLICIT NONE
23
24   !! * Routine/type accessibility
25   PRIVATE
26
27   PUBLIC &
28      & obs_group,         &
29      & obs_group_alloc,   &
30      & obs_group_dealloc, &
31      & obs_group_read,    &
32      & obs_group_check
33
34   !! * Shared Module variables
35   INTEGER, PARAMETER :: jpmaxntypes = 1000   ! Maximum number of obs types for each obs group
36   INTEGER, PARAMETER :: jpmaxnfiles = 1000   ! Maximum number of files for each obs group
37   
38   ! Expected names for observation types with special behaviours (not needed for all observation types)
39   CHARACTER(LEN=8) :: cobsname_sst    = 'SST'  ! Expected variable name for SST
40   CHARACTER(LEN=8) :: cobsname_temp3d = 'POTM' ! Expected variable name for 3D temperature
41   CHARACTER(LEN=8) :: cobsname_sal3d  = 'PSAL' ! Expected variable name for 3D salinity
42   CHARACTER(LEN=8) :: cobsname_uvel3d = 'UVEL' ! Expected variable name for 3D zonal currents
43   CHARACTER(LEN=8) :: cobsname_vvel3d = 'VVEL' ! Expected variable name for 3D meridional currents
44   CHARACTER(LEN=8) :: cobsname_sla    = 'SLA'  ! Expected variable name for SLA
45
46   !! * Type definition for observation groups
47   TYPE obs_group
48      !
49      CHARACTER(LEN=128)                            :: cgroupname    !: Name of obs group (for stdout)
50      CHARACTER(LEN=8),   DIMENSION(:), ALLOCATABLE :: cobstypes     !: Observation types to read from files
51      CHARACTER(LEN=128), DIMENSION(:), ALLOCATABLE :: cobsfiles     !: Observation file names
52      CHARACTER(LEN=128), DIMENSION(:), ALLOCATABLE :: csstbiasfiles !: SST bias input file names
53      CHARACTER(LEN=128)                            :: caltbiasfile  !: Altimeter bias input file name
54      !
55      INTEGER,            DIMENSION(:), ALLOCATABLE :: nprofdavtypes !: Profile data types representing a daily average
56      !
57      INTEGER  :: nobstypes          !: Number of observation types
58      INTEGER  :: nobsfiles          !: Number of observation files
59      INTEGER  :: nextvars           !: Number of extra variables to get
60      INTEGER  :: nsstbiasfiles      !: Number of SST bias files
61      INTEGER  :: navtypes           !: Number of profile data types representing a daily average
62      INTEGER  :: n1dint             !: Type of vertical interpolation method
63      INTEGER  :: n2dint             !: Type of horizontal interpolation method
64      INTEGER  :: nmsshc             !: MSSH correction scheme
65      !
66      LOGICAL  :: lenabled           !: Logical switch for group being processed and not ignored
67      LOGICAL  :: lsurf              !: Logical switch for surface data
68      LOGICAL  :: lprof              !: Logical switch for profile data
69      LOGICAL  :: lsst               !: Logical switch for SST data
70      LOGICAL  :: ltemp3d            !: Logical switch for 3D temperature data
71      LOGICAL  :: lsal3d             !: Logical switch for 3D salinity data
72      LOGICAL  :: lvel3d             !: Logical switch for 3D velocity data
73      LOGICAL  :: lsla               !: Logical switch for SLA data
74      LOGICAL  :: laltbias           !: Logical switch for altimeter bias correction
75      LOGICAL  :: lsstbias           !: Logical switch for SST bias correction
76      LOGICAL  :: lnea               !: Logical switch for rejecting observations near land
77      LOGICAL  :: lbound_reject      !: Logical switch for rejecting obs near the boundary
78      LOGICAL  :: lignmis            !: Logical switch for ignoring missing files
79      LOGICAL  :: ls_at_t            !: Logical switch for computing model S at T obs if not there
80      LOGICAL  :: lnight             !: Logical switch for calculating night-time average
81      LOGICAL  :: loutput_clim       !: Logical switch for writing climatological values to fdbk files
82      LOGICAL  :: ltime_mean_sla_bkg !: Logical switch for applying time mean of SLA background to remove tidal signal
83      LOGICAL  :: lfp_indegs         !: Logical: T=> averaging footprint is in degrees, F=> in metres
84      !
85      REAL(wp) :: ravglamscl         !: E/W diameter of observation footprint (metres/degrees)
86      REAL(wp) :: ravgphiscl         !: N/S diameter of observation footprint (metres/degrees)
87      REAL(wp) :: rmdtcorr           !: MDT correction
88      REAL(wp) :: rmdtcutoff         !: MDT cutoff for computed correction
89      !
90      REAL(wp), POINTER, DIMENSION(:,:,:)   :: rglam  !: Longitudes
91      REAL(wp), POINTER, DIMENSION(:,:,:)   :: rgphi  !: Latitudes
92      REAL(wp), POINTER, DIMENSION(:,:,:,:) :: rmask  !: Land/sea masks
93      !
94      TYPE(obs_surf) :: ssurfdata    !: Initial surface data
95      TYPE(obs_surf) :: ssurfdataqc  !: Surface data after quality control
96      TYPE(obs_prof) :: sprofdata    !: Initial profile data
97      TYPE(obs_prof) :: sprofdataqc  !: Profile data after quality control
98      !
99   END TYPE
100
101CONTAINS
102
103   SUBROUTINE obs_group_alloc( sdobsgroup )
104      !!----------------------------------------------------------------------
105      !!                     ***  ROUTINE obs_group_alloc  ***
106      !!
107      !! ** Purpose : - Allocate data for observation group types
108      !!
109      !! ** Method  : - Allocate arrays
110      !!
111      !! ** Action  : - Allocate arrays
112      !!
113      !!----------------------------------------------------------------------
114      !! * Arguments
115      TYPE(obs_group), INTENT(INOUT) :: sdobsgroup ! Obs group to be allocated
116      !!----------------------------------------------------------------------
117
118      ALLOCATE( sdobsgroup%cobstypes    (sdobsgroup%nobstypes            ), &
119         &      sdobsgroup%cobsfiles    (sdobsgroup%nobsfiles            ), &
120         &      sdobsgroup%csstbiasfiles(sdobsgroup%nsstbiasfiles        ), &
121         &      sdobsgroup%nprofdavtypes(sdobsgroup%navtypes             ), &
122         &      sdobsgroup%rglam        (jpi,jpj,    sdobsgroup%nobstypes), &
123         &      sdobsgroup%rgphi        (jpi,jpj,    sdobsgroup%nobstypes), &
124         &      sdobsgroup%rmask        (jpi,jpj,jpk,sdobsgroup%nobstypes) )
125
126   END SUBROUTINE obs_group_alloc
127
128
129   SUBROUTINE obs_group_dealloc( sdobsgroup )
130      !!----------------------------------------------------------------------
131      !!                     ***  ROUTINE obs_group_dealloc  ***
132      !!
133      !! ** Purpose : - Deallocate data for observation group types
134      !!
135      !! ** Method  : - Deallocate arrays
136      !!
137      !! ** Action  : - Deallocate arrays
138      !!
139      !!----------------------------------------------------------------------
140      !! * Arguments
141      TYPE(obs_group), INTENT(INOUT) :: sdobsgroup ! Obs group to be deallocated
142      !!----------------------------------------------------------------------
143
144      DEALLOCATE( sdobsgroup%cobstypes,     &
145         &        sdobsgroup%cobsfiles,     &
146         &        sdobsgroup%csstbiasfiles, &
147         &        sdobsgroup%nprofdavtypes, &
148         &        sdobsgroup%rglam,         &
149         &        sdobsgroup%rgphi,         &
150         &        sdobsgroup%rmask )
151
152   END SUBROUTINE obs_group_dealloc
153
154
155   SUBROUTINE obs_group_read( sdobsgroup )
156      !!----------------------------------------------------------------------
157      !!                     ***  ROUTINE obs_group_read  ***
158      !!
159      !! ** Purpose : - Read namelist for observation group types
160      !!
161      !! ** Method  : - Read namelist
162      !!
163      !! ** Action  : - Read namelist
164      !!
165      !!----------------------------------------------------------------------
166      !! * Arguments
167      TYPE(obs_group), INTENT(INOUT) :: sdobsgroup ! Obs group to be populated
168      !! * Local variables
169      INTEGER :: ios                               ! Status for namelist read
170      INTEGER :: itype, ifile                      ! Loop counters
171      INTEGER :: jtype, jfile                      ! Loop counters
172      !
173      CHARACTER(LEN=128)                         :: cn_groupname
174      CHARACTER(LEN=8),   DIMENSION(jpmaxntypes) :: cn_obstypes
175      CHARACTER(LEN=128), DIMENSION(jpmaxnfiles) :: cn_obsfiles
176      CHARACTER(LEN=128), DIMENSION(jpmaxnfiles) :: cn_sstbiasfiles
177      CHARACTER(LEN=128)                         :: cn_altbiasfile
178      INTEGER,            DIMENSION(imaxavtypes) :: nn_profdavtypes
179      INTEGER                                    :: nn_1dint
180      INTEGER                                    :: nn_2dint
181      INTEGER                                    :: nn_msshc
182      LOGICAL                                    :: ln_enabled
183      LOGICAL                                    :: ln_surf
184      LOGICAL                                    :: ln_prof
185      LOGICAL                                    :: ln_altbias
186      LOGICAL                                    :: ln_sstbias
187      LOGICAL                                    :: ln_nea
188      LOGICAL                                    :: ln_bound_reject
189      LOGICAL                                    :: ln_ignmis
190      LOGICAL                                    :: ln_s_at_t
191      LOGICAL                                    :: ln_night
192      LOGICAL                                    :: ln_output_clim
193      LOGICAL                                    :: ln_time_mean_sla_bkg
194      LOGICAL                                    :: ln_fp_indegs
195      REAL(wp)                                   :: rn_avglamscl
196      REAL(wp)                                   :: rn_avgphiscl
197      REAL(wp)                                   :: rn_mdtcorr
198      REAL(wp)                                   :: rn_mdtcutoff
199      !!
200      NAMELIST/namobs_dta/cn_groupname, ln_prof, ln_surf, ln_enabled,           &
201         &                cn_obsfiles, cn_obstypes, ln_nea, ln_bound_reject,    &
202         &                ln_ignmis, nn_2dint, nn_1dint, nn_profdavtypes,       &
203         &                ln_fp_indegs, rn_avglamscl, rn_avgphiscl, ln_sstbias, &
204         &                cn_sstbiasfiles, ln_night, ln_altbias,                &
205         &                cn_altbiasfile, nn_msshc, rn_mdtcorr, rn_mdtcutoff,   &
206         &                ln_time_mean_sla_bkg, ln_s_at_t, ln_output_clim
207      !!----------------------------------------------------------------------
208
209      cn_obstypes(:)     = ''
210      cn_obsfiles(:)     = ''
211      cn_sstbiasfiles(:) = ''
212      nn_profdavtypes(:) = -1
213
214      ! There is only one namobs_dta block in namelist_ref -> use it for each group so we do a rewind
215      REWIND(numnam_ref)
216      READ  ( numnam_ref, namobs_dta, IOSTAT = ios, ERR = 901)
217901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namobs_dta in reference namelist' )
218
219      ! Read namobs_dta from namelist_cfg
220      ! WARNING: we don't do a rewind here, each group reads its own namobs_dta block one after another
221      READ  ( numnam_cfg, namobs_dta, IOSTAT = ios, ERR = 902 )
222902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namobs_dta in configuration namelist' )
223      IF(lwm) WRITE( numond, namobs_dta )
224     
225      sdobsgroup%cgroupname = cn_groupname
226      sdobsgroup%lenabled   = ln_enabled
227
228      IF (sdobsgroup%lenabled) THEN
229         sdobsgroup%nobstypes     = 0
230         sdobsgroup%nobsfiles     = 0
231         sdobsgroup%nextvars      = 0
232         sdobsgroup%navtypes      = 0
233         sdobsgroup%nsstbiasfiles = 0
234         sdobsgroup%lsst          = .false.
235         sdobsgroup%ltemp3d       = .false.
236         sdobsgroup%lsal3d        = .false.
237         sdobsgroup%lvel3d        = .false.
238         sdobsgroup%lsla          = .false.
239
240         DO jtype = 1, jpmaxntypes
241            IF ( TRIM(cn_obstypes(jtype)) /= '' ) THEN
242               sdobsgroup%nobstypes = sdobsgroup%nobstypes + 1
243            ENDIF
244         END DO
245         DO jfile = 1, jpmaxnfiles
246            IF ( TRIM(cn_obsfiles(jfile)) /= '' ) THEN
247               sdobsgroup%nobsfiles = sdobsgroup%nobsfiles + 1
248            ENDIF
249         END DO
250         DO jtype = 1, imaxavtypes
251            IF ( nn_profdavtypes(jtype) /= -1 ) THEN
252               sdobsgroup%navtypes = sdobsgroup%navtypes + 1
253            ENDIF
254         END DO
255         DO jfile = 1, jpmaxnfiles
256            IF ( TRIM(cn_sstbiasfiles(jfile)) /= '' ) THEN
257               sdobsgroup%nsstbiasfiles = sdobsgroup%nsstbiasfiles + 1
258            ENDIF
259         END DO
260
261         CALL obs_group_alloc( sdobsgroup )
262
263         itype = 0
264         DO jtype = 1, jpmaxntypes
265            IF ( TRIM(cn_obstypes(jtype)) /= '' ) THEN
266               itype = itype + 1
267               sdobsgroup%cobstypes(itype) = TRIM(cn_obstypes(jtype))
268               IF ( TRIM(sdobsgroup%cobstypes(itype)) == cobsname_sst ) THEN
269                  sdobsgroup%lsst = .true.
270               ELSEIF ( TRIM(sdobsgroup%cobstypes(itype)) == cobsname_temp3d ) THEN
271                  sdobsgroup%ltemp3d = .true.
272                  sdobsgroup%nextvars = sdobsgroup%nextvars + 1
273               ELSEIF ( TRIM(sdobsgroup%cobstypes(itype)) == cobsname_sal3d ) THEN
274                  sdobsgroup%lsal3d = .true.
275               ELSEIF ( (TRIM(sdobsgroup%cobstypes(itype)) == cobsname_uvel3d) .OR. &
276                  &     (TRIM(sdobsgroup%cobstypes(itype)) == cobsname_vvel3d) ) THEN
277                  sdobsgroup%lvel3d = .true.
278                  sdobsgroup%nextvars = sdobsgroup%nextvars + 1
279               ELSEIF ( TRIM(sdobsgroup%cobstypes(itype)) == cobsname_sla ) THEN
280                  sdobsgroup%lsla = .true.
281                  sdobsgroup%nextvars = sdobsgroup%nextvars + 2
282               ENDIF
283               !
284               IF (TRIM(sdobsgroup%cobstypes(itype)) == cobsname_uvel3d) THEN
285                  sdobsgroup%rglam(:,:,itype)   = glamu(:,:)
286                  sdobsgroup%rgphi(:,:,itype)   = gphiu(:,:)
287                  sdobsgroup%rmask(:,:,:,itype) = umask(:,:,:)
288               ELSEIF (TRIM(sdobsgroup%cobstypes(itype)) == cobsname_vvel3d) THEN
289                  sdobsgroup%rglam(:,:,itype)   = glamv(:,:)
290                  sdobsgroup%rgphi(:,:,itype)   = gphiv(:,:)
291                  sdobsgroup%rmask(:,:,:,itype) = vmask(:,:,:)
292               ELSE
293                  sdobsgroup%rglam(:,:,itype)   = glamt(:,:)
294                  sdobsgroup%rgphi(:,:,itype)   = gphit(:,:)
295                  sdobsgroup%rmask(:,:,:,itype) = tmask(:,:,:)
296               ENDIF
297            ENDIF
298         END DO
299         ifile = 0
300         DO jfile = 1, jpmaxnfiles
301            IF ( TRIM(cn_obsfiles(jfile)) /= '' ) THEN
302               ifile = ifile + 1
303               sdobsgroup%cobsfiles(ifile) = TRIM(cn_obsfiles(jfile))
304            ENDIF
305         END DO
306         itype = 0
307         DO jtype = 1, imaxavtypes
308            IF ( nn_profdavtypes(jtype) /= -1 ) THEN
309               itype = itype + 1
310               sdobsgroup%nprofdavtypes(itype) = nn_profdavtypes(jtype)
311            ENDIF
312         END DO
313         ifile = 0
314         DO jfile = 1, jpmaxnfiles
315            IF ( TRIM(cn_sstbiasfiles(jfile)) /= '' ) THEN
316               ifile = ifile + 1
317               sdobsgroup%csstbiasfiles(ifile) = cn_sstbiasfiles(jfile)
318            ENDIF
319         END DO
320
321         sdobsgroup%caltbiasfile       = cn_altbiasfile
322         sdobsgroup%n1dint             = nn_1dint
323         sdobsgroup%n2dint             = nn_2dint
324         sdobsgroup%nmsshc             = nn_msshc
325         sdobsgroup%lsurf              = ln_surf
326         sdobsgroup%lprof              = ln_prof
327         sdobsgroup%laltbias           = ln_altbias
328         sdobsgroup%lsstbias           = ln_sstbias
329         sdobsgroup%lnea               = ln_nea
330         sdobsgroup%lbound_reject      = ln_bound_reject
331         sdobsgroup%lignmis            = ln_ignmis
332         sdobsgroup%ls_at_t            = ln_s_at_t
333         sdobsgroup%lnight             = ln_night
334         sdobsgroup%loutput_clim       = ln_output_clim
335         sdobsgroup%ltime_mean_sla_bkg = ln_time_mean_sla_bkg
336         sdobsgroup%lfp_indegs         = ln_fp_indegs
337         sdobsgroup%ravglamscl         = rn_avglamscl
338         sdobsgroup%ravgphiscl         = rn_avgphiscl
339         sdobsgroup%rmdtcorr           = rn_mdtcorr
340         sdobsgroup%rmdtcutoff         = rn_mdtcutoff
341      ENDIF
342
343   END SUBROUTINE obs_group_read
344
345
346   SUBROUTINE obs_group_check( sdobsgroup, kgroup )
347      !!----------------------------------------------------------------------
348      !!                     ***  ROUTINE obs_group_check  ***
349      !!
350      !! ** Purpose : - Error check observation group types
351      !!
352      !! ** Method  : - Check and print options
353      !!
354      !! ** Action  : - Check and print options
355      !!
356      !!----------------------------------------------------------------------
357      !! * Arguments
358      TYPE(obs_group), INTENT(IN) :: sdobsgroup ! Obs group to be checked
359      INTEGER,         INTENT(IN) :: kgroup     ! Number of group being checked
360      !! * Local variables
361      INTEGER :: jtype, jfile                   ! Loop counters
362      !!----------------------------------------------------------------------
363
364      IF (lwp) THEN
365         WRITE(numout,*)
366         WRITE(numout,*) 'obs_group_check : Options for group ', kgroup, ', ', TRIM(sdobsgroup%cgroupname)
367         WRITE(numout,*) '~~~~~~~~~~~~'
368         WRITE(numout,*) '          Logical switch for group being enabled                  ln_enabled = ', sdobsgroup%lenabled
369         IF ( .NOT. sdobsgroup%lenabled ) THEN
370            WRITE(numout,*) '             Group disabled, will not be used'
371         ELSE
372            WRITE(numout,*) '          Observation types in group:', sdobsgroup%nobstypes
373            DO jtype = 1, sdobsgroup%nobstypes
374               WRITE(numout,*) '             ', TRIM(sdobsgroup%cobstypes(jtype))
375            END DO
376               WRITE(numout,*) '          Observation files in group:', sdobsgroup%nobsfiles
377            DO jfile = 1, sdobsgroup%nobsfiles
378               WRITE(numout,*) '             ', TRIM(sdobsgroup%cobsfiles(jfile))
379            END DO
380            WRITE(numout,*) '          General settings:'
381            WRITE(numout,*) '             Logical switch for surface data                         ln_surf = ', sdobsgroup%lsurf
382            WRITE(numout,*) '             Logical switch for profile data                         ln_prof = ', sdobsgroup%lprof
383            WRITE(numout,*) '             Rejection of observations near land switch               ln_nea = ', sdobsgroup%lnea
384            WRITE(numout,*) '             Rejection of obs near open bdys                 ln_bound_reject = ', sdobsgroup%lbound_reject
385            WRITE(numout,*) '             Logical switch for ignoring missing files             ln_ignmis = ', sdobsgroup%lignmis
386            WRITE(numout,*) '             Type of horizontal interpolation method                nn_2dint = ', sdobsgroup%n2dint
387            IF ( sdobsgroup%n2dint <= 4 ) THEN
388               WRITE(numout,*) '                model counterparts will be interpolated horizontally'
389            ELSE
390               WRITE(numout,*) '                model counterparts will be averaged horizontally'
391            ENDIF
392            WRITE(numout,*) '          Settings only for surface data, which is ', sdobsgroup%lsurf
393            WRITE(numout,*) '             Obs footprint in deg [T] or m [F]                  ln_fp_indegs = ', sdobsgroup%lfp_indegs
394            WRITE(numout,*) '             E/W diameter of obs footprint                      rn_avglamscl = ', sdobsgroup%ravglamscl
395            WRITE(numout,*) '             N/S diameter of obs footprint                      rn_avgphiscl = ', sdobsgroup%ravgphiscl
396            WRITE(numout,*) '             Logical switch for night-time average                  ln_night = ', sdobsgroup%lnight
397            WRITE(numout,*) '          Settings only for profile data, which is ', sdobsgroup%lprof
398            WRITE(numout,*) '             Type of vertical interpolation method                  nn_1dint = ', sdobsgroup%n1dint
399            WRITE(numout,*) '             Daily average types                             nn_profdavtypes = ', sdobsgroup%nprofdavtypes
400            WRITE(numout,*) '          Settings only for SST data, which is ', sdobsgroup%lsst
401            WRITE(numout,*) '             Logical switch for sst bias                          ln_sstbias = ', sdobsgroup%lsstbias
402            IF ( sdobsgroup%lsstbias ) THEN
403               WRITE(numout,*) '             SST bias files in group:'
404               DO jfile = 1, sdobsgroup%nsstbiasfiles
405                  WRITE(numout,*) '                ', TRIM(sdobsgroup%csstbiasfiles(jfile))
406               END DO
407            ENDIF
408            WRITE(numout,*) '          Settings only for SLA data, which is ', sdobsgroup%lsla
409            WRITE(numout,*) '             Logical switch for alt bias                          ln_altbias = ', sdobsgroup%laltbias
410            WRITE(numout,*) '             Alt bias file name                               cn_altbiasfile = ', TRIM(sdobsgroup%caltbiasfile)
411            WRITE(numout,*) '             Logical switch for time-mean of SLA        ln_time_mean_sla_bkg = ', sdobsgroup%ltime_mean_sla_bkg
412            WRITE(numout,*) '             MSSH correction scheme                                 nn_msshc = ', sdobsgroup%nmsshc
413            WRITE(numout,*) '             MDT  correction                                      rn_mdtcorr = ', sdobsgroup%rmdtcorr
414            WRITE(numout,*) '             MDT cutoff for computed correction                 rn_mdtcutoff = ', sdobsgroup%rmdtcutoff
415            WRITE(numout,*) '          Settings only for 3D temperature/salinity data, temperature is ', sdobsgroup%ltemp3d
416            WRITE(numout,*) '                                                             salinity is ', sdobsgroup%lsal3d
417            WRITE(numout,*) '             Logical switch to compute model S at T obs            ln_s_at_t = ', sdobsgroup%ls_at_t
418            WRITE(numout,*) '             Logical switch for writing climat. at obs points ln_output_clim = ', sdobsgroup%loutput_clim
419         ENDIF
420
421         IF ( (       sdobsgroup%lsurf .AND.       sdobsgroup%lprof ) .OR. &
422            & ( .NOT. sdobsgroup%lsurf .AND. .NOT. sdobsgroup%lprof ) ) THEN
423            CALL ctl_stop( ' One and only one of ln_surf or ln_prof must be set per observation group' )
424         ENDIF
425
426         IF ( sdobsgroup%nobstypes == 0 ) THEN
427            CALL ctl_stop( ' No observation types specified for this observation group' )
428         ENDIF
429
430         IF ( sdobsgroup%nobsfiles == 0 ) THEN
431            CALL ctl_stop( ' No observation files specified for this observation group' )
432         ENDIF
433
434         IF ( (sdobsgroup%lsst) .AND. (sdobsgroup%lsstbias) .AND. (sdobsgroup%nsstbiasfiles == 0) ) THEN
435            CALL ctl_stop( ' No SST bias files specified for this observation group' )
436         ENDIF
437
438         IF ( (sdobsgroup%n2dint < 0) .OR. (sdobsgroup%n2dint > 6) ) THEN
439            CALL ctl_stop( ' Invalid horizontal interpolation type' )
440         ENDIF
441
442         IF( (sdobsgroup%n1dint < 0) .OR. (sdobsgroup%n1dint > 1) ) THEN
443            CALL ctl_stop(' Invalid vertical interpolation type')
444         ENDIF
445
446         IF ( (sdobsgroup%n2dint > 4) .AND. (sdobsgroup%n2dint <= 6) ) THEN
447            IF ( sdobsgroup%ravglamscl <= 0._wp ) THEN
448               CALL ctl_stop( ' Incorrect value set for averaging footprint scale rn_avglamscl' )
449            ENDIF
450            IF ( sdobsgroup%ravgphiscl <= 0._wp ) THEN
451               CALL ctl_stop( ' Incorrect value set for averaging footprint scale rn_avgphiscl' )
452            ENDIF
453         ENDIF
454         
455         ! Various other checks of combined options
456
457      ENDIF
458
459   END SUBROUTINE obs_group_check
460
461END MODULE obs_field
Note: See TracBrowser for help on using the repository browser.