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.
diaobs.F90 in branches/2015/dev_r5776_UKMO2_OBS_efficiency_improvs/NEMOGCM/NEMO/OPA_SRC/OBS – NEMO

source: branches/2015/dev_r5776_UKMO2_OBS_efficiency_improvs/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90 @ 5857

Last change on this file since 5857 was 5857, checked in by jenniewaters, 9 years ago

Removing global arrays when ln_grid_global=.false.

  • Property svn:keywords set to Id
File size: 60.0 KB
Line 
1MODULE diaobs
2   !!======================================================================
3   !!                       ***  MODULE diaobs  ***
4   !! Observation diagnostics: Computation of the misfit between data and
5   !!                          their model equivalent
6   !!======================================================================
7
8   !!----------------------------------------------------------------------
9   !!   'key_diaobs' : Switch on the observation diagnostic computation
10   !!----------------------------------------------------------------------
11   !!   dia_obs_init : Reading and prepare observations
12   !!   dia_obs      : Compute model equivalent to observations
13   !!   dia_obs_wri  : Write observational diagnostics
14   !!   ini_date     : Compute the initial date YYYYMMDD.HHMMSS
15   !!   fin_date     : Compute the final date YYYYMMDD.HHMMSS
16   !!----------------------------------------------------------------------
17   !! * Modules used   
18   USE wrk_nemo                 ! Memory Allocation
19   USE par_kind                 ! Precision variables
20   USE in_out_manager           ! I/O manager
21   USE par_oce
22   USE dom_oce                  ! Ocean space and time domain variables
23   USE obs_fbm, ONLY: ln_cl4    ! Class 4 diagnostic switch
24   USE obs_read_prof            ! Reading and allocation of observations (Coriolis)
25   USE obs_read_sla             ! Reading and allocation of SLA observations 
26   USE obs_read_sst             ! Reading and allocation of SST observations 
27   USE obs_readmdt              ! Reading and allocation of MDT for SLA.
28   USE obs_read_seaice          ! Reading and allocation of Sea Ice observations 
29   USE obs_read_vel             ! Reading and allocation of velocity component observations
30   USE obs_prep                 ! Preparation of obs. (grid search etc).
31   USE obs_oper                 ! Observation operators
32   USE obs_write                ! Writing of observation related diagnostics
33   USE obs_grid                 ! Grid searching
34   USE obs_read_altbias         ! Bias treatment for altimeter
35   USE obs_profiles_def         ! Profile data definitions
36   USE obs_profiles             ! Profile data storage
37   USE obs_surf_def             ! Surface data definitions
38   USE obs_sla                  ! SLA data storage
39   USE obs_sst                  ! SST data storage
40   USE obs_seaice               ! Sea Ice data storage
41   USE obs_types                ! Definitions for observation types
42   USE mpp_map                  ! MPP mapping
43   USE lib_mpp                  ! For ctl_warn/stop
44
45   IMPLICIT NONE
46
47   !! * Routine accessibility
48   PRIVATE
49   PUBLIC dia_obs_init, &  ! Initialize and read observations
50      &   dia_obs,      &  ! Compute model equivalent to observations
51      &   dia_obs_wri,  &  ! Write model equivalent to observations
52      &   dia_obs_dealloc  ! Deallocate dia_obs data
53
54   !! * Shared Module variables
55   LOGICAL, PUBLIC, PARAMETER :: &
56#if defined key_diaobs
57      & lk_diaobs = .TRUE.   !: Logical switch for observation diangostics
58#else
59      & lk_diaobs = .FALSE.  !: Logical switch for observation diangostics
60#endif
61
62   !! * Module variables
63   LOGICAL, PUBLIC :: ln_t3d         !: Logical switch for temperature profiles
64   LOGICAL, PUBLIC :: ln_s3d         !: Logical switch for salinity profiles
65   LOGICAL, PUBLIC :: ln_ena         !: Logical switch for the ENACT data set
66   LOGICAL, PUBLIC :: ln_cor         !: Logical switch for the Coriolis data set
67   LOGICAL, PUBLIC :: ln_profb       !: Logical switch for profile feedback datafiles
68   LOGICAL, PUBLIC :: ln_sla         !: Logical switch for sea level anomalies
69   LOGICAL, PUBLIC :: ln_sladt       !: Logical switch for SLA from AVISO files
70   LOGICAL, PUBLIC :: ln_slafb       !: Logical switch for SLA from feedback files
71   LOGICAL, PUBLIC :: ln_sst         !: Logical switch for sea surface temperature
72   LOGICAL, PUBLIC :: ln_reysst      !: Logical switch for Reynolds sea surface temperature
73   LOGICAL, PUBLIC :: ln_ghrsst      !: Logical switch for GHRSST data
74   LOGICAL, PUBLIC :: ln_sstfb       !: Logical switch for SST from feedback files
75   LOGICAL, PUBLIC :: ln_seaice      !: Logical switch for sea ice concentration
76   LOGICAL, PUBLIC :: ln_vel3d       !: Logical switch for velocity component (u,v) observations
77   LOGICAL, PUBLIC :: ln_velavcur    !: Logical switch for raw daily averaged netCDF current meter vel. data
78   LOGICAL, PUBLIC :: ln_velhrcur    !: Logical switch for raw high freq netCDF current meter vel. data
79   LOGICAL, PUBLIC :: ln_velavadcp   !: Logical switch for raw daily averaged netCDF ADCP vel. data
80   LOGICAL, PUBLIC :: ln_velhradcp   !: Logical switch for raw high freq netCDF ADCP vel. data
81   LOGICAL, PUBLIC :: ln_velfb       !: Logical switch for velocities from feedback files
82   LOGICAL, PUBLIC :: ln_ssh         !: Logical switch for sea surface height
83   LOGICAL, PUBLIC :: ln_sss         !: Logical switch for sea surface salinity
84   LOGICAL, PUBLIC :: ln_sstnight    !: Logical switch for night mean SST observations
85   LOGICAL, PUBLIC :: ln_nea         !: Remove observations near land
86   LOGICAL, PUBLIC :: ln_altbias     !: Logical switch for altimeter bias 
87   LOGICAL, PUBLIC :: ln_ignmis      !: Logical switch for ignoring missing files
88   LOGICAL, PUBLIC :: ln_s_at_t      !: Logical switch to compute model S at T observations
89
90   REAL(KIND=dp), PUBLIC :: dobsini   !: Observation window start date YYYYMMDD.HHMMSS
91   REAL(KIND=dp), PUBLIC :: dobsend   !: Observation window end date YYYYMMDD.HHMMSS
92 
93   INTEGER, PUBLIC :: n1dint       !: Vertical interpolation method
94   INTEGER, PUBLIC :: n2dint       !: Horizontal interpolation method
95
96   INTEGER, DIMENSION(imaxavtypes) :: &
97      & endailyavtypes !: ENACT data types which are daily average
98
99   INTEGER, PARAMETER :: MaxNumFiles = 1000
100   LOGICAL, DIMENSION(MaxNumFiles) :: &
101      & ln_profb_ena, & !: Is the feedback files from ENACT data ?
102   !                    !: If so use endailyavtypes
103      & ln_profb_enatim !: Change tim for 820 enact data set.
104   
105   LOGICAL, DIMENSION(MaxNumFiles) :: &
106      & ln_velfb_av   !: Is the velocity feedback files daily average?
107   LOGICAL, DIMENSION(:), ALLOCATABLE :: &
108      & ld_enact     !: Profile data is ENACT so use endailyavtypes
109   LOGICAL, DIMENSION(:), ALLOCATABLE :: &
110      & ld_velav     !: Velocity data is daily averaged
111   LOGICAL, DIMENSION(:), ALLOCATABLE :: &
112      & ld_sstnight  !: SST observation corresponds to night mean
113
114   !!----------------------------------------------------------------------
115   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
116   !! $Id$
117   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
118   !!----------------------------------------------------------------------
119
120CONTAINS
121
122   SUBROUTINE dia_obs_init
123      !!----------------------------------------------------------------------
124      !!                    ***  ROUTINE dia_obs_init  ***
125      !!         
126      !! ** Purpose : Initialize and read observations
127      !!
128      !! ** Method  : Read the namelist and call reading routines
129      !!
130      !! ** Action  : Read the namelist and call reading routines
131      !!
132      !! History :
133      !!        !  06-03  (K. Mogensen) Original code
134      !!        !  06-05  (A. Weaver) Reformatted
135      !!        !  06-10  (A. Weaver) Cleaning and add controls
136      !!        !  07-03  (K. Mogensen) General handling of profiles
137      !!----------------------------------------------------------------------
138
139      IMPLICIT NONE
140
141      !! * Local declarations
142      CHARACTER(len=128) :: enactfiles(MaxNumFiles)
143      CHARACTER(len=128) :: coriofiles(MaxNumFiles)
144      CHARACTER(len=128) :: profbfiles(MaxNumFiles)
145      CHARACTER(len=128) :: sstfiles(MaxNumFiles)     
146      CHARACTER(len=128) :: sstfbfiles(MaxNumFiles) 
147      CHARACTER(len=128) :: slafilesact(MaxNumFiles)     
148      CHARACTER(len=128) :: slafilespas(MaxNumFiles)     
149      CHARACTER(len=128) :: slafbfiles(MaxNumFiles)
150      CHARACTER(len=128) :: seaicefiles(MaxNumFiles)           
151      CHARACTER(len=128) :: velcurfiles(MaxNumFiles) 
152      CHARACTER(len=128) :: veladcpfiles(MaxNumFiles)   
153      CHARACTER(len=128) :: velavcurfiles(MaxNumFiles)
154      CHARACTER(len=128) :: velhrcurfiles(MaxNumFiles)
155      CHARACTER(len=128) :: velavadcpfiles(MaxNumFiles)
156      CHARACTER(len=128) :: velhradcpfiles(MaxNumFiles)
157      CHARACTER(len=128) :: velfbfiles(MaxNumFiles)
158      CHARACTER(LEN=128) :: reysstname
159      CHARACTER(LEN=12)  :: reysstfmt
160      CHARACTER(LEN=128) :: bias_file
161      CHARACTER(LEN=20)  :: datestr=" ", timestr=" "
162      NAMELIST/namobs/ln_ena, ln_cor, ln_profb, ln_t3d, ln_s3d,       &
163         &            ln_sla, ln_sladt, ln_slafb,                     &
164         &            ln_ssh, ln_sst, ln_sstfb, ln_sss, ln_nea,       &
165         &            enactfiles, coriofiles, profbfiles,             &
166         &            slafilesact, slafilespas, slafbfiles,           &
167         &            sstfiles, sstfbfiles,                           &
168         &            ln_seaice, seaicefiles,                         &
169         &            dobsini, dobsend, n1dint, n2dint,               &
170         &            nmsshc, mdtcorr, mdtcutoff,                     &
171         &            ln_reysst, ln_ghrsst, reysstname, reysstfmt,    &
172         &            ln_sstnight,                                    &
173         &            ln_grid_search_lookup,                          &
174         &            grid_search_file, grid_search_res,              &
175         &            ln_grid_global, bias_file, ln_altbias,          &
176         &            endailyavtypes, ln_s_at_t, ln_profb_ena,        &
177         &            ln_vel3d, ln_velavcur, velavcurfiles,           &
178         &            ln_velhrcur, velhrcurfiles,                     &
179         &            ln_velavadcp, velavadcpfiles,                   &
180         &            ln_velhradcp, velhradcpfiles,                   &
181         &            ln_velfb, velfbfiles, ln_velfb_av,              &
182         &            ln_profb_enatim, ln_ignmis, ln_cl4
183
184      INTEGER :: jprofset
185      INTEGER :: jveloset
186      INTEGER :: jvar
187      INTEGER :: jnumenact
188      INTEGER :: jnumcorio
189      INTEGER :: jnumprofb
190      INTEGER :: jnumslaact
191      INTEGER :: jnumslapas
192      INTEGER :: jnumslafb
193      INTEGER :: jnumsst
194      INTEGER :: jnumsstfb
195      INTEGER :: jnumseaice
196      INTEGER :: jnumvelavcur
197      INTEGER :: jnumvelhrcur 
198      INTEGER :: jnumvelavadcp
199      INTEGER :: jnumvelhradcp   
200      INTEGER :: jnumvelfb
201      INTEGER :: ji
202      INTEGER :: jset
203      INTEGER :: ios                 ! Local integer output status for namelist read
204      LOGICAL :: lmask(MaxNumFiles), ll_u3d, ll_v3d
205
206      !-----------------------------------------------------------------------
207      ! Read namelist parameters
208      !-----------------------------------------------------------------------
209
210      enactfiles(:) = ''
211      coriofiles(:) = ''
212      profbfiles(:) = ''
213      slafilesact(:) = ''
214      slafilespas(:) = ''
215      slafbfiles(:) = ''
216      sstfiles(:)   = ''
217      sstfbfiles(:) = ''
218      seaicefiles(:) = ''
219      velcurfiles(:) = ''
220      veladcpfiles(:) = ''
221      velavcurfiles(:) = ''
222      velhrcurfiles(:) = ''
223      velavadcpfiles(:) = ''
224      velhradcpfiles(:) = ''
225      velfbfiles(:) = ''
226      velcurfiles(:) = ''
227      veladcpfiles(:) = ''
228      endailyavtypes(:) = -1
229      endailyavtypes(1) = 820
230      ln_profb_ena(:) = .FALSE.
231      ln_profb_enatim(:) = .TRUE.
232      ln_velfb_av(:) = .FALSE.
233      ln_ignmis = .FALSE.
234     
235      CALL ini_date( dobsini )
236      CALL fin_date( dobsend )
237 
238      ! Read Namelist namobs : control observation diagnostics
239      REWIND( numnam_ref )              ! Namelist namobs in reference namelist : Diagnostic: control observation
240      READ  ( numnam_ref, namobs, IOSTAT = ios, ERR = 901)
241901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namobs in reference namelist', lwp )
242
243      REWIND( numnam_cfg )              ! Namelist namobs in configuration namelist : Diagnostic: control observation
244      READ  ( numnam_cfg, namobs, IOSTAT = ios, ERR = 902 )
245902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namobs in configuration namelist', lwp )
246      IF(lwm) WRITE ( numond, namobs )
247
248      ! Count number of files for each type
249      IF (ln_ena) THEN
250         lmask(:) = .FALSE.
251         WHERE (enactfiles(:) /= '') lmask(:) = .TRUE.
252         jnumenact = COUNT(lmask)
253      ENDIF
254      IF (ln_cor) THEN
255         lmask(:) = .FALSE.
256         WHERE (coriofiles(:) /= '') lmask(:) = .TRUE.
257         jnumcorio = COUNT(lmask)
258      ENDIF
259      IF (ln_profb) THEN
260         lmask(:) = .FALSE.
261         WHERE (profbfiles(:) /= '') lmask(:) = .TRUE.
262         jnumprofb = COUNT(lmask)
263      ENDIF
264      IF (ln_sladt) THEN
265         lmask(:) = .FALSE.
266         WHERE (slafilesact(:) /= '') lmask(:) = .TRUE.
267         jnumslaact = COUNT(lmask)
268         lmask(:) = .FALSE.
269         WHERE (slafilespas(:) /= '') lmask(:) = .TRUE.
270         jnumslapas = COUNT(lmask)
271      ENDIF
272      IF (ln_slafb) THEN
273         lmask(:) = .FALSE.
274         WHERE (slafbfiles(:) /= '') lmask(:) = .TRUE.
275         jnumslafb = COUNT(lmask)
276         lmask(:) = .FALSE.
277      ENDIF
278      IF (ln_ghrsst) THEN
279         lmask(:) = .FALSE.
280         WHERE (sstfiles(:) /= '') lmask(:) = .TRUE.
281         jnumsst = COUNT(lmask)
282      ENDIF     
283      IF (ln_sstfb) THEN
284         lmask(:) = .FALSE.
285         WHERE (sstfbfiles(:) /= '') lmask(:) = .TRUE.
286         jnumsstfb = COUNT(lmask)
287         lmask(:) = .FALSE.
288      ENDIF
289      IF (ln_seaice) THEN
290         lmask(:) = .FALSE.
291         WHERE (seaicefiles(:) /= '') lmask(:) = .TRUE.
292         jnumseaice = COUNT(lmask)
293      ENDIF
294      IF (ln_velavcur) THEN
295         lmask(:) = .FALSE.
296         WHERE (velavcurfiles(:) /= '') lmask(:) = .TRUE.
297         jnumvelavcur = COUNT(lmask)
298      ENDIF
299      IF (ln_velhrcur) THEN
300         lmask(:) = .FALSE.
301         WHERE (velhrcurfiles(:) /= '') lmask(:) = .TRUE.
302         jnumvelhrcur = COUNT(lmask)
303      ENDIF
304      IF (ln_velavadcp) THEN
305         lmask(:) = .FALSE.
306         WHERE (velavadcpfiles(:) /= '') lmask(:) = .TRUE.
307         jnumvelavadcp = COUNT(lmask)
308      ENDIF
309      IF (ln_velhradcp) THEN
310         lmask(:) = .FALSE.
311         WHERE (velhradcpfiles(:) /= '') lmask(:) = .TRUE.
312         jnumvelhradcp = COUNT(lmask)
313      ENDIF
314      IF (ln_velfb) THEN
315         lmask(:) = .FALSE.
316         WHERE (velfbfiles(:) /= '') lmask(:) = .TRUE.
317         jnumvelfb = COUNT(lmask)
318         lmask(:) = .FALSE.
319      ENDIF
320     
321      ! Control print
322      IF(lwp) THEN
323         WRITE(numout,*)
324         WRITE(numout,*) 'dia_obs_init : Observation diagnostic initialization'
325         WRITE(numout,*) '~~~~~~~~~~~~'
326         WRITE(numout,*) '          Namelist namobs : set observation diagnostic parameters' 
327         WRITE(numout,*) '             Logical switch for T profile observations          ln_t3d = ', ln_t3d
328         WRITE(numout,*) '             Logical switch for S profile observations          ln_s3d = ', ln_s3d
329         WRITE(numout,*) '             Logical switch for ENACT insitu data set           ln_ena = ', ln_ena
330         WRITE(numout,*) '             Logical switch for Coriolis insitu data set        ln_cor = ', ln_cor
331         WRITE(numout,*) '             Logical switch for feedback insitu data set      ln_profb = ', ln_profb
332         WRITE(numout,*) '             Logical switch for SLA observations                ln_sla = ', ln_sla
333         WRITE(numout,*) '             Logical switch for AVISO SLA data                ln_sladt = ', ln_sladt
334         WRITE(numout,*) '             Logical switch for feedback SLA data             ln_slafb = ', ln_slafb
335         WRITE(numout,*) '             Logical switch for SSH observations                ln_ssh = ', ln_ssh
336         WRITE(numout,*) '             Logical switch for SST observations                ln_sst = ', ln_sst
337         WRITE(numout,*) '             Logical switch for Reynolds observations        ln_reysst = ', ln_reysst   
338         WRITE(numout,*) '             Logical switch for GHRSST observations          ln_ghrsst = ', ln_ghrsst
339         WRITE(numout,*) '             Logical switch for feedback SST data             ln_sstfb = ', ln_sstfb
340         WRITE(numout,*) '             Logical switch for night-time SST obs         ln_sstnight = ', ln_sstnight
341         WRITE(numout,*) '             Logical switch for SSS observations                ln_sss = ', ln_sss
342         WRITE(numout,*) '             Logical switch for Sea Ice observations         ln_seaice = ', ln_seaice
343         WRITE(numout,*) '             Logical switch for velocity observations         ln_vel3d = ', ln_vel3d
344         WRITE(numout,*) '             Logical switch for velocity daily av. cur.    ln_velavcur = ', ln_velavcur
345         WRITE(numout,*) '             Logical switch for velocity high freq. cur.   ln_velhrcur = ', ln_velhrcur
346         WRITE(numout,*) '             Logical switch for velocity daily av. ADCP   ln_velavadcp = ', ln_velavadcp
347         WRITE(numout,*) '             Logical switch for velocity high freq. ADCP  ln_velhradcp = ', ln_velhradcp
348         WRITE(numout,*) '             Logical switch for feedback velocity data        ln_velfb = ', ln_velfb
349         WRITE(numout,*) '             Global distribtion of observations         ln_grid_global = ',ln_grid_global
350         WRITE(numout,*) &
351   '             Logical switch for obs grid search w/lookup table  ln_grid_search_lookup = ',ln_grid_search_lookup
352         IF (ln_grid_search_lookup) &
353            WRITE(numout,*) '             Grid search lookup file header       grid_search_file = ', grid_search_file
354         IF (ln_ena) THEN
355            DO ji = 1, jnumenact
356               WRITE(numout,'(1X,2A)') '             ENACT input observation file name          enactfiles = ', &
357                  TRIM(enactfiles(ji))
358            END DO
359         ENDIF
360         IF (ln_cor) THEN
361            DO ji = 1, jnumcorio
362               WRITE(numout,'(1X,2A)') '             Coriolis input observation file name       coriofiles = ', &
363                  TRIM(coriofiles(ji))
364            END DO
365         ENDIF
366         IF (ln_profb) THEN
367            DO ji = 1, jnumprofb
368               IF (ln_profb_ena(ji)) THEN
369                  WRITE(numout,'(1X,2A)') '       Enact feedback input observation file name       profbfiles = ', &
370                     TRIM(profbfiles(ji))
371               ELSE
372                  WRITE(numout,'(1X,2A)') '             Feedback input observation file name       profbfiles = ', &
373                     TRIM(profbfiles(ji))
374               ENDIF
375               WRITE(numout,'(1X,2A)') '       Enact feedback input time setting switch    ln_profb_enatim = ', ln_profb_enatim(ji)
376            END DO
377         ENDIF
378         IF (ln_sladt) THEN
379            DO ji = 1, jnumslaact
380               WRITE(numout,'(1X,2A)') '             Active SLA input observation file name    slafilesact = ', &
381                  TRIM(slafilesact(ji))
382            END DO
383            DO ji = 1, jnumslapas
384               WRITE(numout,'(1X,2A)') '             Passive SLA input observation file name   slafilespas = ', &
385                  TRIM(slafilespas(ji))
386            END DO
387         ENDIF
388         IF (ln_slafb) THEN
389            DO ji = 1, jnumslafb
390               WRITE(numout,'(1X,2A)') '             Feedback SLA input observation file name   slafbfiles = ', &
391                  TRIM(slafbfiles(ji))
392            END DO
393         ENDIF
394         IF (ln_ghrsst) THEN
395            DO ji = 1, jnumsst
396               WRITE(numout,'(1X,2A)') '             GHRSST input observation file name           sstfiles = ', &
397                  TRIM(sstfiles(ji))
398            END DO
399         ENDIF
400         IF (ln_sstfb) THEN
401            DO ji = 1, jnumsstfb
402               WRITE(numout,'(1X,2A)') '             Feedback SST input observation file name   sstfbfiles = ', &
403                  TRIM(sstfbfiles(ji))
404            END DO
405         ENDIF
406         IF (ln_seaice) THEN
407            DO ji = 1, jnumseaice
408               WRITE(numout,'(1X,2A)') '             Sea Ice input observation file name       seaicefiles = ', &
409                  TRIM(seaicefiles(ji))
410            END DO
411         ENDIF
412         IF (ln_velavcur) THEN
413            DO ji = 1, jnumvelavcur
414               WRITE(numout,'(1X,2A)') '             Vel. cur. daily av. input file name     velavcurfiles = ', &
415                  TRIM(velavcurfiles(ji))
416            END DO
417         ENDIF
418         IF (ln_velhrcur) THEN
419            DO ji = 1, jnumvelhrcur
420               WRITE(numout,'(1X,2A)') '             Vel. cur. high freq. input file name    velhvcurfiles = ', &
421                  TRIM(velhrcurfiles(ji))
422            END DO
423         ENDIF
424         IF (ln_velavadcp) THEN
425            DO ji = 1, jnumvelavadcp
426               WRITE(numout,'(1X,2A)') '             Vel. ADCP daily av. input file name    velavadcpfiles = ', &
427                  TRIM(velavadcpfiles(ji))
428            END DO
429         ENDIF
430         IF (ln_velhradcp) THEN
431            DO ji = 1, jnumvelhradcp
432               WRITE(numout,'(1X,2A)') '             Vel. ADCP high freq. input file name   velhvadcpfiles = ', &
433                  TRIM(velhradcpfiles(ji))
434            END DO
435         ENDIF
436         IF (ln_velfb) THEN
437            DO ji = 1, jnumvelfb
438               IF (ln_velfb_av(ji)) THEN
439                  WRITE(numout,'(1X,2A)') '             Vel. feedback daily av. input file name    velfbfiles = ', &
440                     TRIM(velfbfiles(ji))
441               ELSE
442                  WRITE(numout,'(1X,2A)') '             Vel. feedback input observation file name  velfbfiles = ', &
443                     TRIM(velfbfiles(ji))
444               ENDIF
445            END DO
446         ENDIF
447         WRITE(numout,*) '             Initial date in window YYYYMMDD.HHMMSS        dobsini = ', dobsini
448         WRITE(numout,*) '             Final date in window YYYYMMDD.HHMMSS          dobsend = ', dobsend
449         WRITE(numout,*) '             Type of vertical interpolation method          n1dint = ', n1dint
450         WRITE(numout,*) '             Type of horizontal interpolation method        n2dint = ', n2dint
451         WRITE(numout,*) '             Rejection of observations near land swithch    ln_nea = ', ln_nea
452         WRITE(numout,*) '             MSSH correction scheme                         nmsshc = ', nmsshc
453         WRITE(numout,*) '             MDT  correction                               mdtcorr = ', mdtcorr
454         WRITE(numout,*) '             MDT cutoff for computed correction          mdtcutoff = ', mdtcutoff
455         WRITE(numout,*) '             Logical switch for alt bias                ln_altbias = ', ln_altbias
456         WRITE(numout,*) '             Logical switch for ignoring missing files   ln_ignmis = ', ln_ignmis
457         WRITE(numout,*) '             ENACT daily average types                             = ',endailyavtypes
458
459      ENDIF
460     
461      IF ( ln_vel3d .AND. ( .NOT. ln_grid_global ) ) THEN
462         CALL ctl_stop( 'Velocity data only works with ln_grid_global=.true.' )
463         RETURN
464      ENDIF
465
466      CALL obs_typ_init
467
468      IF ( ln_grid_global ) THEN     
469         CALL mppmap_init
470      ENDIF
471     
472      ! Parameter control
473#if defined key_diaobs
474      IF ( ( .NOT. ln_t3d ).AND.( .NOT. ln_s3d ).AND.( .NOT. ln_sla ).AND. &
475         & ( .NOT. ln_vel3d ).AND.                                         &
476         & ( .NOT. ln_ssh ).AND.( .NOT. ln_sst ).AND.( .NOT. ln_sss ).AND. &
477         & ( .NOT. ln_seaice ).AND.( .NOT. ln_vel3d ) ) THEN
478         IF(lwp) WRITE(numout,cform_war)
479         IF(lwp) WRITE(numout,*) ' key_diaobs is activated but logical flags', &
480            &                    ' ln_t3d, ln_s3d, ln_sla, ln_ssh, ln_sst, ln_sss, ln_seaice, ln_vel3d are all set to .FALSE.'
481         nwarn = nwarn + 1
482      ENDIF
483#endif
484
485      CALL obs_grid_setup( )
486      IF ( ( n1dint < 0 ).OR.( n1dint > 1 ) ) THEN
487         CALL ctl_stop(' Choice of vertical (1D) interpolation method', &
488            &                    ' is not available')
489      ENDIF
490      IF ( ( n2dint < 0 ).OR.( n2dint > 4 ) ) THEN
491         CALL ctl_stop(' Choice of horizontal (2D) interpolation method', &
492            &                    ' is not available')
493      ENDIF
494
495      !-----------------------------------------------------------------------
496      ! Depending on switches read the various observation types
497      !-----------------------------------------------------------------------
498      !  - Temperature/salinity profiles
499
500      IF ( ln_t3d .OR. ln_s3d ) THEN
501
502         ! Set the number of variables for profiles to 2 (T and S)
503         nprofvars = 2
504         ! Set the number of extra variables for profiles to 1 (insitu temp).
505         nprofextr = 1
506
507         ! Count how may insitu data sets we have and allocate data.
508         jprofset = 0
509         IF ( ln_ena ) jprofset = jprofset + 1
510         IF ( ln_cor ) jprofset = jprofset + 1
511         IF ( ln_profb ) jprofset = jprofset + jnumprofb
512         nprofsets = jprofset
513         IF ( nprofsets > 0 ) THEN
514            ALLOCATE(ld_enact(nprofsets))
515            ALLOCATE(profdata(nprofsets))
516            ALLOCATE(prodatqc(nprofsets))
517         ENDIF
518
519         jprofset = 0
520         
521         ! ENACT insitu data
522
523         IF ( ln_ena ) THEN
524
525            jprofset = jprofset + 1
526           
527            ld_enact(jprofset) = .TRUE.
528
529            CALL obs_rea_pro_dri( 1, profdata(jprofset),          &
530               &                  jnumenact, enactfiles(1:jnumenact), &
531               &                  nprofvars, nprofextr,        &
532               &                  nitend-nit000+2,             &
533               &                  dobsini, dobsend, ln_t3d, ln_s3d, &
534               &                  ln_ignmis, ln_s_at_t, .TRUE., .FALSE., &
535               &                  kdailyavtypes = endailyavtypes )
536
537            DO jvar = 1, 2
538
539               CALL obs_prof_staend( profdata(jprofset), jvar )
540
541            END DO
542
543            CALL obs_pre_pro( profdata(jprofset), prodatqc(jprofset),   &
544               &              ln_t3d, ln_s3d, ln_nea, &
545               &              kdailyavtypes=endailyavtypes )
546           
547         ENDIF
548
549         ! Coriolis insitu data
550
551         IF ( ln_cor ) THEN
552           
553            jprofset = jprofset + 1
554
555            ld_enact(jprofset) = .FALSE.
556
557            CALL obs_rea_pro_dri( 2, profdata(jprofset),          &
558               &                  jnumcorio, coriofiles(1:jnumcorio), &
559               &                  nprofvars, nprofextr,        &
560               &                  nitend-nit000+2,             &
561               &                  dobsini, dobsend, ln_t3d, ln_s3d, &
562               &                  ln_ignmis, ln_s_at_t, .FALSE., .FALSE. )
563
564            DO jvar = 1, 2
565
566               CALL obs_prof_staend( profdata(jprofset), jvar )
567
568            END DO
569
570            CALL obs_pre_pro( profdata(jprofset), prodatqc(jprofset),   &
571                 &            ln_t3d, ln_s3d, ln_nea )
572           
573         ENDIF
574 
575         ! Feedback insitu data
576
577         IF ( ln_profb ) THEN
578           
579            DO jset = 1, jnumprofb
580               
581               jprofset = jprofset + 1
582               ld_enact (jprofset) = ln_profb_ena(jset)
583
584               CALL obs_rea_pro_dri( 0, profdata(jprofset),          &
585                  &                  1, profbfiles(jset:jset), &
586                  &                  nprofvars, nprofextr,        &
587                  &                  nitend-nit000+2,             &
588                  &                  dobsini, dobsend, ln_t3d, ln_s3d, &
589                  &                  ln_ignmis, ln_s_at_t, &
590                  &                  ld_enact(jprofset).AND.&
591                  &                  ln_profb_enatim(jset), &
592                  &                  .FALSE., kdailyavtypes = endailyavtypes )
593               
594               DO jvar = 1, 2
595                 
596                  CALL obs_prof_staend( profdata(jprofset), jvar )
597                 
598               END DO
599               
600               IF ( ld_enact(jprofset) ) THEN
601                  CALL obs_pre_pro( profdata(jprofset), prodatqc(jprofset),   &
602                     &              ln_t3d, ln_s3d, ln_nea, &
603                     &              kdailyavtypes = endailyavtypes )
604               ELSE
605                  CALL obs_pre_pro( profdata(jprofset), prodatqc(jprofset),   &
606                     &              ln_t3d, ln_s3d, ln_nea )
607               ENDIF
608               
609            END DO
610
611         ENDIF
612
613      ENDIF
614
615      !  - Sea level anomalies
616      IF ( ln_sla ) THEN
617        ! Set the number of variables for sla to 1
618         nslavars = 1
619
620         ! Set the number of extra variables for sla to 2
621         nslaextr = 2
622         
623         ! Set the number of sla data sets to 2
624         nslasets = 0
625         IF ( ln_sladt ) THEN
626            nslasets = nslasets + 2
627         ENDIF
628         IF ( ln_slafb ) THEN
629            nslasets = nslasets + jnumslafb
630         ENDIF
631         
632         ALLOCATE(sladata(nslasets))
633         ALLOCATE(sladatqc(nslasets))
634         sladata(:)%nsurf=0
635         sladatqc(:)%nsurf=0
636
637         nslasets = 0
638
639         ! AVISO SLA data
640
641         IF ( ln_sladt ) THEN
642
643            ! Active SLA observations
644           
645            nslasets = nslasets + 1
646           
647            CALL obs_rea_sla( 1, sladata(nslasets), jnumslaact, &
648               &              slafilesact(1:jnumslaact), &
649               &              nslavars, nslaextr, nitend-nit000+2, &
650               &              dobsini, dobsend, ln_ignmis, .FALSE. )
651            CALL obs_pre_sla( sladata(nslasets), sladatqc(nslasets), &
652               &              ln_sla, ln_nea )
653           
654            ! Passive SLA observations
655           
656            nslasets = nslasets + 1
657           
658            CALL obs_rea_sla( 1, sladata(nslasets), jnumslapas, &
659               &              slafilespas(1:jnumslapas), &
660               &              nslavars, nslaextr, nitend-nit000+2, &
661               &              dobsini, dobsend, ln_ignmis, .FALSE. )
662           
663            CALL obs_pre_sla( sladata(nslasets), sladatqc(nslasets), &
664               &              ln_sla, ln_nea )
665
666         ENDIF
667         
668         ! Feedback SLA data
669
670         IF ( ln_slafb ) THEN
671
672            DO jset = 1, jnumslafb
673           
674               nslasets = nslasets + 1
675           
676               CALL obs_rea_sla( 0, sladata(nslasets), 1, &
677                  &              slafbfiles(jset:jset), &
678                  &              nslavars, nslaextr, nitend-nit000+2, &
679                  &              dobsini, dobsend, ln_ignmis, .FALSE. )
680               CALL obs_pre_sla( sladata(nslasets), sladatqc(nslasets), &
681                  &              ln_sla, ln_nea )
682
683            END DO               
684
685         ENDIF
686         
687         CALL obs_rea_mdt( nslasets, sladatqc, n2dint )
688           
689         ! read in altimeter bias
690         
691         IF ( ln_altbias ) THEN     
692            CALL obs_rea_altbias ( nslasets, sladatqc, n2dint, bias_file )
693         ENDIF
694     
695      ENDIF
696
697      !  - Sea surface height
698      IF ( ln_ssh ) THEN
699         IF(lwp) WRITE(numout,*) ' SSH currently not available'
700      ENDIF
701
702      !  - Sea surface temperature
703      IF ( ln_sst ) THEN
704
705         ! Set the number of variables for sst to 1
706         nsstvars = 1
707
708         ! Set the number of extra variables for sst to 0
709         nsstextr = 0
710
711         nsstsets = 0
712
713         IF (ln_reysst) nsstsets = nsstsets + 1
714         IF (ln_ghrsst) nsstsets = nsstsets + 1
715         IF ( ln_sstfb ) THEN
716            nsstsets = nsstsets + jnumsstfb
717         ENDIF
718
719         ALLOCATE(sstdata(nsstsets))
720         ALLOCATE(sstdatqc(nsstsets))
721         ALLOCATE(ld_sstnight(nsstsets))
722         sstdata(:)%nsurf=0
723         sstdatqc(:)%nsurf=0   
724         ld_sstnight(:)=.false.
725
726         nsstsets = 0
727
728         IF (ln_reysst) THEN
729
730            nsstsets = nsstsets + 1
731
732            ld_sstnight(nsstsets) = ln_sstnight
733
734            CALL obs_rea_sst_rey( reysstname, reysstfmt, sstdata(nsstsets), &
735               &                  nsstvars, nsstextr, &
736               &                  nitend-nit000+2, dobsini, dobsend )
737            CALL obs_pre_sst( sstdata(nsstsets), sstdatqc(nsstsets), ln_sst, &
738               &              ln_nea )
739
740        ENDIF
741       
742        IF (ln_ghrsst) THEN
743       
744            nsstsets = nsstsets + 1
745
746            ld_sstnight(nsstsets) = ln_sstnight
747         
748            CALL obs_rea_sst( 1, sstdata(nsstsets), jnumsst, &
749               &              sstfiles(1:jnumsst), &
750               &              nsstvars, nsstextr, nitend-nit000+2, &
751               &              dobsini, dobsend, ln_ignmis, .FALSE. )
752            CALL obs_pre_sst( sstdata(nsstsets), sstdatqc(nsstsets), ln_sst, &
753               &              ln_nea )
754
755        ENDIF
756               
757         ! Feedback SST data
758
759         IF ( ln_sstfb ) THEN
760
761            DO jset = 1, jnumsstfb
762           
763               nsstsets = nsstsets + 1
764
765               ld_sstnight(nsstsets) = ln_sstnight
766           
767               CALL obs_rea_sst( 0, sstdata(nsstsets), 1, &
768                  &              sstfbfiles(jset:jset), &
769                  &              nsstvars, nsstextr, nitend-nit000+2, &
770                  &              dobsini, dobsend, ln_ignmis, .FALSE. )
771               CALL obs_pre_sst( sstdata(nsstsets), sstdatqc(nsstsets), &
772                  &              ln_sst, ln_nea )
773
774            END DO               
775
776         ENDIF
777
778      ENDIF
779
780      !  - Sea surface salinity
781      IF ( ln_sss ) THEN
782         IF(lwp) WRITE(numout,*) ' SSS currently not available'
783      ENDIF
784
785      !  - Sea Ice Concentration
786     
787      IF ( ln_seaice ) THEN
788
789         ! Set the number of variables for seaice to 1
790         nseaicevars = 1
791
792         ! Set the number of extra variables for seaice to 0
793         nseaiceextr = 0
794         
795         ! Set the number of data sets to 1
796         nseaicesets = 1
797
798         ALLOCATE(seaicedata(nseaicesets))
799         ALLOCATE(seaicedatqc(nseaicesets))
800         seaicedata(:)%nsurf=0
801         seaicedatqc(:)%nsurf=0
802
803         CALL obs_rea_seaice( 1, seaicedata(nseaicesets), jnumseaice, &
804            &                 seaicefiles(1:jnumseaice), &
805            &                 nseaicevars, nseaiceextr, nitend-nit000+2, &
806            &                 dobsini, dobsend, ln_ignmis, .FALSE. )
807
808         CALL obs_pre_seaice( seaicedata(nseaicesets), seaicedatqc(nseaicesets), &
809            &                 ln_seaice, ln_nea )
810 
811      ENDIF
812
813      IF (ln_vel3d) THEN
814
815         ! Set the number of variables for profiles to 2 (U and V)
816         nvelovars = 2
817
818         ! Set the number of extra variables for profiles to 2 to store
819         ! rotation parameters
820         nveloextr = 2
821
822         jveloset = 0
823         
824         IF ( ln_velavcur ) jveloset = jveloset + 1
825         IF ( ln_velhrcur ) jveloset = jveloset + 1
826         IF ( ln_velavadcp ) jveloset = jveloset + 1
827         IF ( ln_velhradcp ) jveloset = jveloset + 1
828         IF (ln_velfb) jveloset = jveloset + jnumvelfb
829
830         nvelosets = jveloset
831         IF ( nvelosets > 0 ) THEN
832            ALLOCATE( velodata(nvelosets) )
833            ALLOCATE( veldatqc(nvelosets) )
834            ALLOCATE( ld_velav(nvelosets) )
835         ENDIF
836         
837         jveloset = 0
838         
839         ! Daily averaged data
840
841         IF ( ln_velavcur ) THEN
842           
843            jveloset = jveloset + 1
844           
845            ld_velav(jveloset) = .TRUE.
846           
847            CALL obs_rea_vel_dri( 1, velodata(jveloset), jnumvelavcur, &
848               &                  velavcurfiles(1:jnumvelavcur), &
849               &                  nvelovars, nveloextr, &
850               &                  nitend-nit000+2,              &
851               &                  dobsini, dobsend, ln_ignmis, &
852               &                  ld_velav(jveloset), &
853               &                  .FALSE. )
854           
855            DO jvar = 1, 2
856               CALL obs_prof_staend( velodata(jveloset), jvar )
857            END DO
858           
859            CALL obs_pre_vel( velodata(jveloset), veldatqc(jveloset), &
860               &              ln_vel3d, ln_nea, ld_velav(jveloset) )
861           
862         ENDIF
863
864         ! High frequency data
865
866         IF ( ln_velhrcur ) THEN
867           
868            jveloset = jveloset + 1
869           
870            ld_velav(jveloset) = .FALSE.
871               
872            CALL obs_rea_vel_dri( 1, velodata(jveloset), jnumvelhrcur, &
873               &                  velhrcurfiles(1:jnumvelhrcur), &
874               &                  nvelovars, nveloextr, &
875               &                  nitend-nit000+2,              &
876               &                  dobsini, dobsend, ln_ignmis, &
877               &                  ld_velav(jveloset), &
878               &                  .FALSE. )
879           
880            DO jvar = 1, 2
881               CALL obs_prof_staend( velodata(jveloset), jvar )
882            END DO
883           
884            CALL obs_pre_vel( velodata(jveloset), veldatqc(jveloset), &
885               &              ln_vel3d, ln_nea, ld_velav(jveloset) )
886           
887         ENDIF
888
889         ! Daily averaged data
890
891         IF ( ln_velavadcp ) THEN
892           
893            jveloset = jveloset + 1
894           
895            ld_velav(jveloset) = .TRUE.
896           
897            CALL obs_rea_vel_dri( 1, velodata(jveloset), jnumvelavadcp, &
898               &                  velavadcpfiles(1:jnumvelavadcp), &
899               &                  nvelovars, nveloextr, &
900               &                  nitend-nit000+2,              &
901               &                  dobsini, dobsend, ln_ignmis, &
902               &                  ld_velav(jveloset), &
903               &                  .FALSE. )
904           
905            DO jvar = 1, 2
906               CALL obs_prof_staend( velodata(jveloset), jvar )
907            END DO
908           
909            CALL obs_pre_vel( velodata(jveloset), veldatqc(jveloset), &
910               &              ln_vel3d, ln_nea, ld_velav(jveloset) )
911           
912         ENDIF
913
914         ! High frequency data
915
916         IF ( ln_velhradcp ) THEN
917           
918            jveloset = jveloset + 1
919           
920            ld_velav(jveloset) = .FALSE.
921               
922            CALL obs_rea_vel_dri( 1, velodata(jveloset), jnumvelhradcp, &
923               &                  velhradcpfiles(1:jnumvelhradcp), &
924               &                  nvelovars, nveloextr, &
925               &                  nitend-nit000+2,              &
926               &                  dobsini, dobsend, ln_ignmis, &
927               &                  ld_velav(jveloset), &
928               &                  .FALSE. )
929           
930            DO jvar = 1, 2
931               CALL obs_prof_staend( velodata(jveloset), jvar )
932            END DO
933           
934            CALL obs_pre_vel( velodata(jveloset), veldatqc(jveloset), &
935               &              ln_vel3d, ln_nea, ld_velav(jveloset) )
936           
937         ENDIF
938
939         IF ( ln_velfb ) THEN
940
941            DO jset = 1, jnumvelfb
942           
943               jveloset = jveloset + 1
944
945               ld_velav(jveloset) = ln_velfb_av(jset)
946               
947               CALL obs_rea_vel_dri( 0, velodata(jveloset), 1, &
948                  &                  velfbfiles(jset:jset), &
949                  &                  nvelovars, nveloextr, &
950                  &                  nitend-nit000+2,              &
951                  &                  dobsini, dobsend, ln_ignmis, &
952                  &                  ld_velav(jveloset), &
953                  &                  .FALSE. )
954               
955               DO jvar = 1, 2
956                  CALL obs_prof_staend( velodata(jveloset), jvar )
957               END DO
958               
959               CALL obs_pre_vel( velodata(jveloset), veldatqc(jveloset), &
960                  &              ln_vel3d, ln_nea, ld_velav(jveloset) )
961
962
963            END DO
964           
965         ENDIF
966
967      ENDIF
968     
969   END SUBROUTINE dia_obs_init
970
971   SUBROUTINE dia_obs( kstp )
972      !!----------------------------------------------------------------------
973      !!                    ***  ROUTINE dia_obs  ***
974      !!         
975      !! ** Purpose : Call the observation operators on each time step
976      !!
977      !! ** Method  : Call the observation operators on each time step to
978      !!              compute the model equivalent of the following date:
979      !!               - T profiles
980      !!               - S profiles
981      !!               - Sea surface height (referenced to a mean)
982      !!               - Sea surface temperature
983      !!               - Sea surface salinity
984      !!               - Velocity component (U,V) profiles
985      !!
986      !! ** Action  :
987      !!
988      !! History :
989      !!        !  06-03  (K. Mogensen) Original code
990      !!        !  06-05  (K. Mogensen) Reformatted
991      !!        !  06-10  (A. Weaver) Cleaning
992      !!        !  07-03  (K. Mogensen) General handling of profiles
993      !!        !  07-04  (G. Smith) Generalized surface operators
994      !!        !  08-10  (M. Valdivieso) obs operator for velocity profiles
995      !!----------------------------------------------------------------------
996      !! * Modules used
997      USE dom_oce, ONLY : &             ! Ocean space and time domain variables
998         & rdt,           &                       
999         & gdept_1d,       &             
1000         & tmask, umask, vmask                           
1001      USE phycst, ONLY : &              ! Physical constants
1002         & rday                         
1003      USE oce, ONLY : &                 ! Ocean dynamics and tracers variables
1004         & tsn,  &             
1005         & un, vn,  &
1006         & sshn
1007#if defined  key_lim3
1008      USE ice, ONLY : &                     ! LIM Ice model variables
1009         & frld
1010#endif
1011#if defined key_lim2
1012      USE ice_2, ONLY : &                     ! LIM Ice model variables
1013         & frld
1014#endif
1015      IMPLICIT NONE
1016
1017      !! * Arguments
1018      INTEGER, INTENT(IN) :: kstp                         ! Current timestep
1019      !! * Local declarations
1020      INTEGER :: idaystp                ! Number of timesteps per day
1021      INTEGER :: jprofset               ! Profile data set loop variable
1022      INTEGER :: jslaset                ! SLA data set loop variable
1023      INTEGER :: jsstset                ! SST data set loop variable
1024      INTEGER :: jseaiceset             ! sea ice data set loop variable
1025      INTEGER :: jveloset               ! velocity profile data loop variable
1026      INTEGER :: jvar                   ! Variable number   
1027#if ! defined key_lim2 && ! defined key_lim3
1028      REAL(wp), POINTER, DIMENSION(:,:) :: frld   
1029#endif
1030      CHARACTER(LEN=20) :: datestr=" ",timestr=" "
1031 
1032#if ! defined key_lim2 && ! defined key_lim3
1033      CALL wrk_alloc(jpi,jpj,frld) 
1034#endif
1035
1036      IF(lwp) THEN
1037         WRITE(numout,*)
1038         WRITE(numout,*) 'dia_obs : Call the observation operators', kstp
1039         WRITE(numout,*) '~~~~~~~'
1040      ENDIF
1041
1042      idaystp = NINT( rday / rdt )
1043
1044      !-----------------------------------------------------------------------
1045      ! No LIM => frld == 0.0_wp
1046      !-----------------------------------------------------------------------
1047#if ! defined key_lim2 && ! defined key_lim3
1048      frld(:,:) = 0.0_wp
1049#endif
1050      !-----------------------------------------------------------------------
1051      ! Depending on switches call various observation operators
1052      !-----------------------------------------------------------------------
1053
1054      !  - Temperature/salinity profiles
1055      IF ( ln_t3d .OR. ln_s3d ) THEN
1056         DO jprofset = 1, nprofsets
1057            IF ( ld_enact(jprofset) ) THEN
1058               CALL obs_pro_opt( prodatqc(jprofset),                     &
1059                  &              kstp, jpi, jpj, jpk, nit000, idaystp,   &
1060                  &              tsn(:,:,:,jp_tem), tsn(:,:,:,jp_sal),   &
1061                  &              gdept_1d, tmask, n1dint, n2dint,        &
1062                  &              kdailyavtypes = endailyavtypes )
1063            ELSE
1064               CALL obs_pro_opt( prodatqc(jprofset),                     &
1065                  &              kstp, jpi, jpj, jpk, nit000, idaystp,   &
1066                  &              tsn(:,:,:,jp_tem), tsn(:,:,:,jp_sal),   &
1067                  &              gdept_1d, tmask, n1dint, n2dint              )
1068            ENDIF
1069         END DO
1070      ENDIF
1071
1072      !  - Sea surface anomaly
1073      IF ( ln_sla ) THEN
1074         DO jslaset = 1, nslasets
1075            CALL obs_sla_opt( sladatqc(jslaset),            &
1076               &              kstp, jpi, jpj, nit000, sshn, &
1077               &              tmask(:,:,1), n2dint )
1078         END DO         
1079      ENDIF
1080
1081      !  - Sea surface temperature
1082      IF ( ln_sst ) THEN
1083         DO jsstset = 1, nsstsets
1084            CALL obs_sst_opt( sstdatqc(jsstset),                &
1085               &              kstp, jpi, jpj, nit000, idaystp,  &
1086               &              tsn(:,:,1,jp_tem), tmask(:,:,1),  &
1087               &              n2dint, ld_sstnight(jsstset) )
1088         END DO
1089      ENDIF
1090
1091      !  - Sea surface salinity
1092      IF ( ln_sss ) THEN
1093         IF(lwp) WRITE(numout,*) ' SSS currently not available'
1094      ENDIF
1095
1096#if defined key_lim2 || defined key_lim3
1097      IF ( ln_seaice ) THEN
1098         DO jseaiceset = 1, nseaicesets
1099            CALL obs_seaice_opt( seaicedatqc(jseaiceset),      &
1100               &              kstp, jpi, jpj, nit000, 1.-frld, &
1101               &              tmask(:,:,1), n2dint )
1102         END DO
1103      ENDIF     
1104#endif
1105
1106      !  - Velocity profiles
1107      IF ( ln_vel3d ) THEN
1108         DO jveloset = 1, nvelosets
1109           ! zonal component of velocity
1110           CALL obs_vel_opt( veldatqc(jveloset), kstp, jpi, jpj, jpk, &
1111              &              nit000, idaystp, un, vn, gdept_1d, umask, vmask, &
1112                             n1dint, n2dint, ld_velav(jveloset) )
1113         END DO
1114      ENDIF
1115
1116#if ! defined key_lim2 && ! defined key_lim3
1117      CALL wrk_dealloc(jpi,jpj,frld) 
1118#endif
1119
1120   END SUBROUTINE dia_obs
1121 
1122   SUBROUTINE dia_obs_wri 
1123      !!----------------------------------------------------------------------
1124      !!                    ***  ROUTINE dia_obs_wri  ***
1125      !!         
1126      !! ** Purpose : Call observation diagnostic output routines
1127      !!
1128      !! ** Method  : Call observation diagnostic output routines
1129      !!
1130      !! ** Action  :
1131      !!
1132      !! History :
1133      !!        !  06-03  (K. Mogensen) Original code
1134      !!        !  06-05  (K. Mogensen) Reformatted
1135      !!        !  06-10  (A. Weaver) Cleaning
1136      !!        !  07-03  (K. Mogensen) General handling of profiles
1137      !!        !  08-09  (M. Valdivieso) Velocity component (U,V) profiles
1138      !!----------------------------------------------------------------------
1139      IMPLICIT NONE
1140
1141      !! * Local declarations
1142
1143      INTEGER :: jprofset                 ! Profile data set loop variable
1144      INTEGER :: jveloset                 ! Velocity data set loop variable
1145      INTEGER :: jslaset                  ! SLA data set loop variable
1146      INTEGER :: jsstset                  ! SST data set loop variable
1147      INTEGER :: jseaiceset               ! Sea Ice data set loop variable
1148      INTEGER :: jset
1149      INTEGER :: jfbini
1150      CHARACTER(LEN=20) :: datestr=" ",timestr=" "
1151      CHARACTER(LEN=10) :: cdtmp
1152      !-----------------------------------------------------------------------
1153      ! Depending on switches call various observation output routines
1154      !-----------------------------------------------------------------------
1155
1156      !  - Temperature/salinity profiles
1157
1158      IF( ln_t3d .OR. ln_s3d ) THEN
1159
1160         ! Copy data from prodatqc to profdata structures
1161         DO jprofset = 1, nprofsets
1162
1163            CALL obs_prof_decompress( prodatqc(jprofset), &
1164                 &                    profdata(jprofset), .TRUE., numout )
1165
1166         END DO
1167
1168         ! Write the profiles.
1169
1170         jprofset = 0
1171
1172         ! ENACT insitu data
1173
1174         IF ( ln_ena ) THEN
1175           
1176            jprofset = jprofset + 1
1177
1178            CALL obs_wri_p3d( 'enact', profdata(jprofset) )
1179
1180         ENDIF
1181
1182         ! Coriolis insitu data
1183
1184         IF ( ln_cor ) THEN
1185           
1186            jprofset = jprofset + 1
1187
1188            CALL obs_wri_p3d( 'corio', profdata(jprofset) )
1189           
1190         ENDIF
1191         
1192         ! Feedback insitu data
1193
1194         IF ( ln_profb ) THEN
1195
1196            jfbini = jprofset + 1
1197
1198            DO jprofset = jfbini, nprofsets
1199               
1200               jset = jprofset - jfbini + 1
1201               WRITE(cdtmp,'(A,I2.2)')'profb_',jset
1202               CALL obs_wri_p3d( cdtmp, profdata(jprofset) )
1203
1204            END DO
1205
1206         ENDIF
1207
1208      ENDIF
1209
1210      !  - Sea surface anomaly
1211      IF ( ln_sla ) THEN
1212
1213         ! Copy data from sladatqc to sladata structures
1214         DO jslaset = 1, nslasets
1215
1216              CALL obs_surf_decompress( sladatqc(jslaset), &
1217                 &                    sladata(jslaset), .TRUE., numout )
1218
1219         END DO
1220
1221         jslaset = 0 
1222
1223         ! Write the AVISO SLA data
1224
1225         IF ( ln_sladt ) THEN
1226           
1227            jslaset = 1
1228            CALL obs_wri_sla( 'aviso_act', sladata(jslaset) )
1229            jslaset = 2
1230            CALL obs_wri_sla( 'aviso_pas', sladata(jslaset) )
1231
1232         ENDIF
1233
1234         IF ( ln_slafb ) THEN
1235           
1236            jfbini = jslaset + 1
1237
1238            DO jslaset = jfbini, nslasets
1239               
1240               jset = jslaset - jfbini + 1
1241               WRITE(cdtmp,'(A,I2.2)')'slafb_',jset
1242               CALL obs_wri_sla( cdtmp, sladata(jslaset) )
1243
1244            END DO
1245
1246         ENDIF
1247
1248      ENDIF
1249
1250      !  - Sea surface temperature
1251      IF ( ln_sst ) THEN
1252
1253         ! Copy data from sstdatqc to sstdata structures
1254         DO jsstset = 1, nsstsets
1255     
1256              CALL obs_surf_decompress( sstdatqc(jsstset), &
1257                 &                    sstdata(jsstset), .TRUE., numout )
1258
1259         END DO
1260
1261         jsstset = 0 
1262
1263         ! Write the AVISO SST data
1264
1265         IF ( ln_reysst ) THEN
1266           
1267            jsstset = jsstset + 1
1268            CALL obs_wri_sst( 'reynolds', sstdata(jsstset) )
1269
1270         ENDIF
1271
1272         IF ( ln_ghrsst ) THEN
1273           
1274            jsstset = jsstset + 1
1275            CALL obs_wri_sst( 'ghr', sstdata(jsstset) )
1276
1277         ENDIF
1278
1279         IF ( ln_sstfb ) THEN
1280           
1281            jfbini = jsstset + 1
1282
1283            DO jsstset = jfbini, nsstsets
1284               
1285               jset = jsstset - jfbini + 1
1286               WRITE(cdtmp,'(A,I2.2)')'sstfb_',jset
1287               CALL obs_wri_sst( cdtmp, sstdata(jsstset) )
1288
1289            END DO
1290
1291         ENDIF
1292
1293      ENDIF
1294
1295      !  - Sea surface salinity
1296      IF ( ln_sss ) THEN
1297         IF(lwp) WRITE(numout,*) ' SSS currently not available'
1298      ENDIF
1299
1300      !  - Sea Ice Concentration
1301      IF ( ln_seaice ) THEN
1302
1303         ! Copy data from seaicedatqc to seaicedata structures
1304         DO jseaiceset = 1, nseaicesets
1305
1306              CALL obs_surf_decompress( seaicedatqc(jseaiceset), &
1307                 &                    seaicedata(jseaiceset), .TRUE., numout )
1308
1309         END DO
1310
1311         ! Write the Sea Ice data
1312         DO jseaiceset = 1, nseaicesets
1313     
1314            WRITE(cdtmp,'(A,I2.2)')'seaicefb_',jseaiceset
1315            CALL obs_wri_seaice( cdtmp, seaicedata(jseaiceset) )
1316
1317         END DO
1318
1319      ENDIF
1320     
1321      ! Velocity data
1322      IF( ln_vel3d ) THEN
1323
1324         ! Copy data from veldatqc to velodata structures
1325         DO jveloset = 1, nvelosets
1326
1327            CALL obs_prof_decompress( veldatqc(jveloset), &
1328                 &                    velodata(jveloset), .TRUE., numout )
1329
1330         END DO
1331
1332         ! Write the profiles.
1333
1334         jveloset = 0
1335
1336         ! Daily averaged data
1337
1338         IF ( ln_velavcur ) THEN
1339           
1340            jveloset = jveloset + 1
1341
1342            CALL obs_wri_vel( 'velavcurr', velodata(jveloset), n2dint )
1343
1344         ENDIF
1345
1346         ! High frequency data
1347
1348         IF ( ln_velhrcur ) THEN
1349           
1350            jveloset = jveloset + 1
1351
1352            CALL obs_wri_vel( 'velhrcurr', velodata(jveloset), n2dint )
1353
1354         ENDIF
1355
1356         ! Daily averaged data
1357
1358         IF ( ln_velavadcp ) THEN
1359           
1360            jveloset = jveloset + 1
1361
1362            CALL obs_wri_vel( 'velavadcp', velodata(jveloset), n2dint )
1363
1364         ENDIF
1365
1366         ! High frequency data
1367
1368         IF ( ln_velhradcp ) THEN
1369           
1370            jveloset = jveloset + 1
1371           
1372            CALL obs_wri_vel( 'velhradcp', velodata(jveloset), n2dint )
1373               
1374         ENDIF
1375
1376         ! Feedback velocity data
1377
1378         IF ( ln_velfb ) THEN
1379
1380            jfbini = jveloset + 1
1381
1382            DO jveloset = jfbini, nvelosets
1383               
1384               jset = jveloset - jfbini + 1
1385               WRITE(cdtmp,'(A,I2.2)')'velfb_',jset
1386               CALL obs_wri_vel( cdtmp, velodata(jveloset), n2dint )
1387
1388            END DO
1389
1390         ENDIF
1391         
1392      ENDIF
1393
1394   END SUBROUTINE dia_obs_wri
1395
1396   SUBROUTINE dia_obs_dealloc
1397      IMPLICIT NONE
1398      !!----------------------------------------------------------------------
1399      !!                    *** ROUTINE dia_obs_dealloc ***
1400      !!
1401      !!  ** Purpose : To deallocate data to enable the obs_oper online loop.
1402      !!               Specifically: dia_obs_init --> dia_obs --> dia_obs_wri
1403      !!
1404      !!  ** Method : Clean up various arrays left behind by the obs_oper.
1405      !!
1406      !!  ** Action :
1407      !!
1408      !!----------------------------------------------------------------------
1409      !! obs_grid deallocation
1410      CALL obs_grid_deallocate
1411
1412      !! diaobs deallocation
1413      IF ( nprofsets > 0 ) THEN
1414          DEALLOCATE(ld_enact, &
1415                  &  profdata, &
1416                  &  prodatqc)
1417      END IF
1418      IF ( ln_sla ) THEN
1419          DEALLOCATE(sladata, &
1420                  &  sladatqc)
1421      END IF
1422      IF ( ln_seaice ) THEN
1423          DEALLOCATE(sladata, &
1424                  &  sladatqc)
1425      END IF
1426      IF ( ln_sst ) THEN
1427          DEALLOCATE(sstdata, &
1428                  &  sstdatqc)
1429      END IF
1430      IF ( ln_vel3d ) THEN
1431          DEALLOCATE(ld_velav, &
1432                  &  velodata, &
1433                  &  veldatqc)
1434      END IF
1435   END SUBROUTINE dia_obs_dealloc
1436
1437   SUBROUTINE ini_date( ddobsini )
1438      !!----------------------------------------------------------------------
1439      !!                    ***  ROUTINE ini_date  ***
1440      !!         
1441      !! ** Purpose : Get initial data in double precision YYYYMMDD.HHMMSS format
1442      !!
1443      !! ** Method  : Get initial data in double precision YYYYMMDD.HHMMSS format
1444      !!
1445      !! ** Action  : Get initial data in double precision YYYYMMDD.HHMMSS format
1446      !!
1447      !! History :
1448      !!        !  06-03  (K. Mogensen)  Original code
1449      !!        !  06-05  (K. Mogensen)  Reformatted
1450      !!        !  06-10  (A. Weaver) Cleaning
1451      !!        !  06-10  (G. Smith) Calculates initial date the same as method for final date
1452      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2
1453      !!----------------------------------------------------------------------
1454      USE phycst, ONLY : &            ! Physical constants
1455         & rday
1456!      USE daymod, ONLY : &            ! Time variables
1457!         & nmonth_len           
1458      USE dom_oce, ONLY : &           ! Ocean space and time domain variables
1459         & rdt
1460
1461      IMPLICIT NONE
1462
1463      !! * Arguments
1464      REAL(KIND=dp), INTENT(OUT) :: ddobsini                         ! Initial date in YYYYMMDD.HHMMSS
1465
1466      !! * Local declarations
1467      INTEGER :: iyea        ! date - (year, month, day, hour, minute)
1468      INTEGER :: imon
1469      INTEGER :: iday
1470      INTEGER :: ihou
1471      INTEGER :: imin
1472      INTEGER :: imday         ! Number of days in month.
1473      REAL(KIND=wp) :: zdayfrc ! Fraction of day
1474
1475      INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year
1476
1477      !!----------------------------------------------------------------------
1478      !! Initial date initialization (year, month, day, hour, minute)
1479      !! (This assumes that the initial date is for 00z))
1480      !!----------------------------------------------------------------------
1481      iyea =   ndate0 / 10000
1482      imon = ( ndate0 - iyea * 10000 ) / 100
1483      iday =   ndate0 - iyea * 10000 - imon * 100
1484      ihou = 0
1485      imin = 0
1486
1487      !!----------------------------------------------------------------------
1488      !! Compute number of days + number of hours + min since initial time
1489      !!----------------------------------------------------------------------
1490      iday = iday + ( nit000 -1 ) * rdt / rday
1491      zdayfrc = ( nit000 -1 ) * rdt / rday
1492      zdayfrc = zdayfrc - aint(zdayfrc)
1493      ihou = int( zdayfrc * 24 )
1494      imin = int( (zdayfrc * 24 - ihou) * 60 )
1495
1496      !!-----------------------------------------------------------------------
1497      !! Convert number of days (iday) into a real date
1498      !!----------------------------------------------------------------------
1499
1500      CALL calc_month_len( iyea, imonth_len )
1501     
1502      DO WHILE ( iday > imonth_len(imon) )
1503         iday = iday - imonth_len(imon)
1504         imon = imon + 1 
1505         IF ( imon > 12 ) THEN
1506            imon = 1
1507            iyea = iyea + 1
1508            CALL calc_month_len( iyea, imonth_len )  ! update month lengths
1509         ENDIF
1510      END DO
1511
1512      !!----------------------------------------------------------------------
1513      !! Convert it into YYYYMMDD.HHMMSS format.
1514      !!----------------------------------------------------------------------
1515      ddobsini = iyea * 10000_dp + imon * 100_dp + &
1516         &       iday + ihou * 0.01_dp + imin * 0.0001_dp
1517
1518
1519   END SUBROUTINE ini_date
1520
1521   SUBROUTINE fin_date( ddobsfin )
1522      !!----------------------------------------------------------------------
1523      !!                    ***  ROUTINE fin_date  ***
1524      !!         
1525      !! ** Purpose : Get final data in double precision YYYYMMDD.HHMMSS format
1526      !!
1527      !! ** Method  : Get final data in double precision YYYYMMDD.HHMMSS format
1528      !!
1529      !! ** Action  : Get final data in double precision YYYYMMDD.HHMMSS format
1530      !!
1531      !! History :
1532      !!        !  06-03  (K. Mogensen)  Original code
1533      !!        !  06-05  (K. Mogensen)  Reformatted
1534      !!        !  06-10  (A. Weaver) Cleaning
1535      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2
1536      !!----------------------------------------------------------------------
1537      USE phycst, ONLY : &            ! Physical constants
1538         & rday
1539!      USE daymod, ONLY : &            ! Time variables
1540!         & nmonth_len               
1541      USE dom_oce, ONLY : &           ! Ocean space and time domain variables
1542         & rdt
1543
1544      IMPLICIT NONE
1545
1546      !! * Arguments
1547      REAL(KIND=dp), INTENT(OUT) :: ddobsfin                   ! Final date in YYYYMMDD.HHMMSS
1548
1549      !! * Local declarations
1550      INTEGER :: iyea        ! date - (year, month, day, hour, minute)
1551      INTEGER :: imon
1552      INTEGER :: iday
1553      INTEGER :: ihou
1554      INTEGER :: imin
1555      INTEGER :: imday         ! Number of days in month.
1556      REAL(KIND=wp) :: zdayfrc       ! Fraction of day
1557         
1558      INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year
1559           
1560      !-----------------------------------------------------------------------
1561      ! Initial date initialization (year, month, day, hour, minute)
1562      ! (This assumes that the initial date is for 00z)
1563      !-----------------------------------------------------------------------
1564      iyea =   ndate0 / 10000
1565      imon = ( ndate0 - iyea * 10000 ) / 100
1566      iday =   ndate0 - iyea * 10000 - imon * 100
1567      ihou = 0
1568      imin = 0
1569     
1570      !-----------------------------------------------------------------------
1571      ! Compute number of days + number of hours + min since initial time
1572      !-----------------------------------------------------------------------
1573      iday    = iday +  nitend  * rdt / rday
1574      zdayfrc =  nitend  * rdt / rday
1575      zdayfrc = zdayfrc - AINT( zdayfrc )
1576      ihou    = INT( zdayfrc * 24 )
1577      imin    = INT( ( zdayfrc * 24 - ihou ) * 60 )
1578
1579      !-----------------------------------------------------------------------
1580      ! Convert number of days (iday) into a real date
1581      !----------------------------------------------------------------------
1582
1583      CALL calc_month_len( iyea, imonth_len )
1584     
1585      DO WHILE ( iday > imonth_len(imon) )
1586         iday = iday - imonth_len(imon)
1587         imon = imon + 1 
1588         IF ( imon > 12 ) THEN
1589            imon = 1
1590            iyea = iyea + 1
1591            CALL calc_month_len( iyea, imonth_len )  ! update month lengths
1592         ENDIF
1593      END DO
1594
1595      !-----------------------------------------------------------------------
1596      ! Convert it into YYYYMMDD.HHMMSS format
1597      !-----------------------------------------------------------------------
1598      ddobsfin = iyea * 10000_dp + imon * 100_dp    + iday &
1599         &     + ihou * 0.01_dp  + imin * 0.0001_dp
1600
1601    END SUBROUTINE fin_date
1602   
1603END MODULE diaobs
Note: See TracBrowser for help on using the repository browser.