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_surf_def.F90 in branches/UKMO/dev_r4650_general_vert_coord_obsoper_pfts/NEMOGCM/NEMO/OPA_SRC/OBS – NEMO

source: branches/UKMO/dev_r4650_general_vert_coord_obsoper_pfts/NEMOGCM/NEMO/OPA_SRC/OBS/obs_surf_def.F90 @ 8105

Last change on this file since 8105 was 6990, checked in by kingr, 8 years ago

Added code from nemo3.4 OBS branch to allow rejection of observations near open boundaries.

File size: 16.4 KB
Line 
1MODULE obs_surf_def
2   !!=====================================================================
3   !!                       ***  MODULE  obs_surf_def  ***
4   !! Observation diagnostics: Storage handling for surface observation
5   !!                          arrays and additional flags etc.
6   !!                          This module only defines the data type and
7   !!                          operations on the data type. There is no
8   !!                          actual data in the module.
9   !!=====================================================================
10
11   !!----------------------------------------------------------------------
12   !!   obs_surf            : F90 type containing the surface information
13   !!   obs_surf_alloc      : Allocates surface data arrays
14   !!   obs_surf_dealloc    : Deallocates surface data arrays
15   !!   obs_surf_compress   : Extract sub-information from a obs_surf type
16   !!                         to a new obs_surf type
17   !!   obs_surf_decompress : Reinsert sub-information from a obs_surf type
18   !!                         into the original obs_surf type
19   !!----------------------------------------------------------------------
20   !! * Modules used
21   USE par_kind, ONLY : & ! Precision variables
22      & wp         
23   USE obs_mpp, ONLY : &  ! MPP tools
24      obs_mpp_sum_integer
25
26   IMPLICIT NONE
27
28   !! * Routine/type accessibility
29   PRIVATE
30
31   PUBLIC &
32      & obs_surf,           &
33      & obs_surf_alloc,     &
34      & obs_surf_dealloc,   &
35      & obs_surf_compress,  &
36      & obs_surf_decompress
37
38   !! * Type definition for surface observation type
39
40   TYPE obs_surf
41
42      ! Bookkeeping
43
44      INTEGER :: nsurf      !: Local number of surface data within window
45      INTEGER :: nsurfmpp   !: Global number of surface data within window
46      INTEGER :: nvar       !: Number of variables at observation points
47      INTEGER :: nextra     !: Number of extra fields at observation points
48      INTEGER :: nstp       !: Number of time steps
49      INTEGER :: npi        !: Number of 3D grid points
50      INTEGER :: npj
51      INTEGER :: nsurfup    !: Observation counter used in obs_oper
52      INTEGER :: nrec       !: Number of surface observation records in window
53
54      ! Arrays with size equal to the number of surface observations
55
56      INTEGER, POINTER, DIMENSION(:) :: &
57         & mi,   &        !: i-th grid coord. for interpolating to surface observation
58         & mj,   &        !: j-th grid coord. for interpolating to surface observation
59         & mt,   &        !: time record number for gridded data
60         & nsidx,&        !: Surface observation number
61         & nsfil,&        !: Surface observation number in file
62         & nyea, &        !: Year of surface observation
63         & nmon, &        !: Month of surface observation
64         & nday, &        !: Day of surface observation
65         & nhou, &        !: Hour of surface observation
66         & nmin, &        !: Minute of surface observation
67         & mstp, &        !: Time step nearest to surface observation
68         & nqc,  &        !: Surface observation qc flag
69         & ntyp           !: Type of surface observation product
70
71      CHARACTER(LEN=8), POINTER, DIMENSION(:) :: &
72         & cwmo           !: WMO indentifier
73         
74      REAL(KIND=wp), POINTER, DIMENSION(:) :: &
75         & rlam, &        !: Longitude coordinate of surface observation
76         & rphi           !: Latitude coordinate of surface observation
77
78      REAL(KIND=wp), POINTER, DIMENSION(:,:) :: &
79         & robs, &        !: Surface observation
80         & rmod           !: Model counterpart of the surface observation vector
81
82      REAL(KIND=wp), POINTER, DIMENSION(:,:) :: &
83         & rext           !: Extra fields interpolated to observation points
84
85      REAL(KIND=wp), POINTER, DIMENSION(:,:) :: &
86         & vdmean         !: Time averaged of model field
87
88      ! Arrays with size equal to the number of time steps in the window
89
90      INTEGER, POINTER, DIMENSION(:) :: &
91         & nsstp,     &   !: Local number of surface observations per time step
92         & nsstpmpp       !: Global number of surface observations per time step
93
94      ! Arrays with size equal to the number of observation records in the window
95      INTEGER, POINTER, DIMENSION(:) :: &
96         & mrecstp   ! Time step of the records
97
98      ! Arrays used to store source indices when
99      ! compressing obs_surf derived types
100     
101      ! Array with size nsurf
102
103      INTEGER, POINTER, DIMENSION(:) :: &
104         & nsind          !: Source indices of surface data in compressed data
105
106      ! Is this a gridded product?
107     
108      LOGICAL :: lgrid
109
110   END TYPE obs_surf
111
112   !!----------------------------------------------------------------------
113   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
114   !! $Id$
115   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
116   !!----------------------------------------------------------------------
117
118CONTAINS
119   
120   SUBROUTINE obs_surf_alloc( surf, ksurf, kvar, kextra, kstp, kpi, kpj )
121      !!----------------------------------------------------------------------
122      !!                     ***  ROUTINE obs_surf_alloc  ***
123      !!                     
124      !! ** Purpose : - Allocate data for surface data arrays
125      !!
126      !! ** Method  : - Fortran-90 dynamic arrays
127      !!
128      !! History :
129      !!        !  07-03  (K. Mogensen, A. Weaver, E. Remy, S. Ricci) original
130      !!----------------------------------------------------------------------
131      !! * Arguments
132      TYPE(obs_surf), INTENT(INOUT) ::  surf      ! Surface data to be allocated
133      INTEGER, INTENT(IN) :: ksurf   ! Number of surface observations
134      INTEGER, INTENT(IN) :: kvar    ! Number of surface variables
135      INTEGER, INTENT(IN) :: kextra  ! Number of extra fields at observation points
136      INTEGER, INTENT(IN) :: kstp    ! Number of time steps
137      INTEGER, INTENT(IN) :: kpi     ! Number of 3D grid points
138      INTEGER, INTENT(IN) :: kpj
139
140      !!* Local variables
141      INTEGER :: ji
142
143      ! Set bookkeeping variables
144
145      surf%nsurf    = ksurf
146      surf%nsurfmpp = 0
147      surf%nextra   = kextra
148      surf%nvar     = kvar
149      surf%nstp     = kstp
150      surf%npi      = kpi
151      surf%npj      = kpj
152     
153      ! Allocate arrays of number of surface data size
154
155      ALLOCATE( &
156         & surf%mi(ksurf),      &
157         & surf%mj(ksurf),      &
158         & surf%mt(ksurf),      &
159         & surf%nsidx(ksurf),   &
160         & surf%nsfil(ksurf),   &
161         & surf%nyea(ksurf),    &
162         & surf%nmon(ksurf),    &
163         & surf%nday(ksurf),    &
164         & surf%nhou(ksurf),    &
165         & surf%nmin(ksurf),    &
166         & surf%mstp(ksurf),    &
167         & surf%nqc(ksurf),     &
168         & surf%ntyp(ksurf),    &
169         & surf%cwmo(ksurf),    &
170         & surf%rlam(ksurf),    &
171         & surf%rphi(ksurf),    &
172         & surf%nsind(ksurf)    &
173         & )
174
175      surf%mt(:) = -1
176
177
178      ! Allocate arrays of number of surface data size * number of variables
179
180      ALLOCATE( & 
181         & surf%robs(ksurf,kvar), &
182         & surf%rmod(ksurf,kvar)  &
183         & )   
184
185      ! Allocate arrays of number of extra fields at observation points
186
187      ALLOCATE( & 
188         & surf%rext(ksurf,kextra) &
189         & )
190
191      surf%rext(:,:) = 0.0_wp 
192
193      ! Allocate arrays of number of time step size
194
195      ALLOCATE( &
196         & surf%nsstp(kstp),     &
197         & surf%nsstpmpp(kstp)   &
198         & )
199
200      ! Allocate arrays of size number of grid points
201
202      ALLOCATE( &
203         & surf%vdmean(kpi,kpj) &
204         & )
205
206      ! Set defaults for compression indices
207     
208      DO ji = 1, ksurf
209         surf%nsind(ji) = ji
210      END DO
211     
212      ! Set defaults for number of observations per time step
213
214      surf%nsstp(:)     = 0
215      surf%nsstpmpp(:)  = 0
216
217      ! Set the observation counter used in obs_oper
218
219      surf%nsurfup     = 0
220     
221      ! Not gridded by default
222         
223      surf%lgrid       = .FALSE.
224             
225   END SUBROUTINE obs_surf_alloc
226
227   SUBROUTINE obs_surf_dealloc( surf )
228      !!----------------------------------------------------------------------
229      !!                     ***  ROUTINE obs_surf_dealloc  ***
230      !!                     
231      !! ** Purpose : - Deallocate data for surface data arrays
232      !!
233      !! ** Method  : - Fortran-90 dynamic arrays
234      !!
235      !! History :
236      !!        !  07-03  (K. Mogensen, A. Weaver, E. Remy, S. Ricci) original
237      !!----------------------------------------------------------------------
238      !! * Arguments
239      TYPE(obs_surf), INTENT(INOUT) :: &
240         & surf      ! Surface data to be allocated
241
242      !!* Local variables
243
244      ! Deallocate arrays of number of surface data size
245
246      DEALLOCATE( &
247         & surf%mi,      &
248         & surf%mj,      &
249         & surf%mt,      &
250         & surf%nsidx,   &
251         & surf%nsfil,   &
252         & surf%nyea,    &
253         & surf%nmon,    &
254         & surf%nday,    &
255         & surf%nhou,    &
256         & surf%nmin,    &
257         & surf%mstp,    &
258         & surf%nqc,     &
259         & surf%ntyp,    &
260         & surf%cwmo,    &
261         & surf%rlam,    &
262         & surf%rphi,    &
263         & surf%nsind    &
264         & )
265
266      ! Allocate arrays of number of surface data size * number of variables
267
268      DEALLOCATE( & 
269         & surf%robs,    &
270         & surf%rmod     &
271         & )
272
273      ! Deallocate arrays of number of extra fields at observation points
274
275      DEALLOCATE( & 
276         & surf%rext &
277         & )
278
279      ! Deallocate arrays of size number of grid points size times
280      ! number of variables
281
282      DEALLOCATE( &
283         & surf%vdmean &
284         & )
285
286      ! Deallocate arrays of number of time step size
287
288      DEALLOCATE( &
289         & surf%nsstp,     &
290         & surf%nsstpmpp   &
291         & )
292
293   END SUBROUTINE obs_surf_dealloc
294
295   SUBROUTINE obs_surf_compress( surf, newsurf, lallocate, kumout, lvalid )
296      !!----------------------------------------------------------------------
297      !!                     ***  ROUTINE obs_surf_compress  ***
298      !!                     
299      !! ** Purpose : - Extract sub-information from a obs_surf type
300      !!                into a new obs_surf type
301      !!
302      !! ** Method  : - The data is copied from surf to new surf.
303      !!                In the case of lvalid being present only the
304      !!                selected data will be copied.
305      !!                If lallocate is true the data in the newsurf is
306      !!                allocated either with the same number of elements
307      !!                as surf or with only the subset of elements defined
308      !!                by the optional selection.
309      !!
310      !! History :
311      !!        !  07-03  (K. Mogensen, A. Weaver, E. Remy, S. Ricci) original
312      !!----------------------------------------------------------------------
313      !! * Arguments
314      TYPE(obs_surf), INTENT(IN)    :: surf      ! Original surface data
315      TYPE(obs_surf), INTENT(INOUT) :: newsurf   ! New surface data with a subset of the original data
316      LOGICAL :: lallocate     ! Allocate newsurf data
317      INTEGER,INTENT(IN) :: kumout        ! Fortran unit for messages
318      LOGICAL, OPTIONAL, INTENT(in), DIMENSION(:) :: &
319         & lvalid         ! Valid of surface observations
320     
321      !!* Local variables
322      INTEGER :: insurf
323      INTEGER :: ji
324      INTEGER :: jk
325      LOGICAL, DIMENSION(:), ALLOCATABLE :: llvalid
326
327      ! Count how many elements there should be in the new data structure
328
329      IF ( PRESENT(lvalid) ) THEN
330         insurf = 0
331         DO ji = 1, surf%nsurf
332            IF ( lvalid(ji) ) THEN
333               insurf = insurf + 1
334            ENDIF
335         END DO
336      ELSE
337         insurf = surf%nsurf
338      ENDIF
339
340      ! Optionally allocate data in the new data structure
341
342      IF ( lallocate ) THEN
343         CALL obs_surf_alloc( newsurf,  insurf, surf%nvar, &
344            & surf%nextra, surf%nstp, surf%npi, surf%npj )
345      ENDIF
346
347      ! Allocate temporary valid array to unify the code for both cases
348
349      ALLOCATE( llvalid(surf%nsurf) )
350      IF ( PRESENT(lvalid) ) THEN
351         llvalid(:)  = lvalid(:)
352      ELSE
353         llvalid(:)  = .TRUE.
354      ENDIF
355
356      ! Setup bookkeeping variables
357
358      insurf = 0
359
360      ! Loop over source surface data
361
362      DO ji = 1, surf%nsurf
363
364         IF ( llvalid(ji) ) THEN
365
366            ! Copy the header information
367
368            insurf = insurf + 1
369
370            newsurf%mi(insurf)    = surf%mi(ji)
371            newsurf%mj(insurf)    = surf%mj(ji)
372            newsurf%mt(insurf)    = surf%mt(ji)
373            newsurf%nsidx(insurf) = surf%nsidx(ji)
374            newsurf%nsfil(insurf) = surf%nsfil(ji)
375            newsurf%nyea(insurf)  = surf%nyea(ji)
376            newsurf%nmon(insurf)  = surf%nmon(ji)
377            newsurf%nday(insurf)  = surf%nday(ji)
378            newsurf%nhou(insurf)  = surf%nhou(ji)
379            newsurf%nmin(insurf)  = surf%nmin(ji)
380            newsurf%mstp(insurf)  = surf%mstp(ji)
381            newsurf%nqc(insurf)   = surf%nqc(ji)
382            newsurf%ntyp(insurf)  = surf%ntyp(ji)
383            newsurf%cwmo(insurf)  = surf%cwmo(ji)
384            newsurf%rlam(insurf)  = surf%rlam(ji)
385            newsurf%rphi(insurf)  = surf%rphi(ji)
386
387            DO jk = 1, surf%nvar
388
389               newsurf%robs(insurf,jk)  = surf%robs(ji,jk)
390               newsurf%rmod(insurf,jk)  = surf%rmod(ji,jk)
391               
392            END DO
393
394            DO jk = 1, surf%nextra
395
396               newsurf%rext(insurf,jk) = surf%rext(ji,jk)
397
398            END DO
399           
400            ! nsind is the index of the original surface data
401           
402            newsurf%nsind(insurf) = ji
403
404         ENDIF
405
406      END DO
407
408      ! Update MPP counters
409
410      newsurf%nsurf = insurf
411      CALL obs_mpp_sum_integer ( newsurf%nsurf, newsurf%nsurfmpp )
412
413      ! Set book keeping variables which do not depend on number of obs.
414
415      newsurf%nstp  = surf%nstp
416     
417      ! Set gridded stuff
418     
419      newsurf%mt(insurf)    = surf%mt(ji)
420 
421      ! Deallocate temporary data
422
423      DEALLOCATE( llvalid )
424     
425   END SUBROUTINE obs_surf_compress
426
427   SUBROUTINE obs_surf_decompress( surf, oldsurf, ldeallocate, kumout )
428      !!----------------------------------------------------------------------
429      !!                     ***  ROUTINE obs_surf_decompress  ***
430      !!                     
431      !! ** Purpose : - Copy back information to original surface data type
432      !!
433      !! ** Method  : - Reinsert updated information from a previous
434      !!                copied/compressed surface data type into the original
435      !!                surface data and optionally deallocate the surface
436      !!                data input
437      !!
438      !! History :
439      !!        !  07-03  (K. Mogensen, A. Weaver, E. Remy, S. Ricci) original
440      !!----------------------------------------------------------------------
441      !! * Arguments
442      TYPE(obs_surf),INTENT(INOUT) :: surf       ! Updated surface data
443      TYPE(obs_surf),INTENT(INOUT) :: oldsurf    ! Original surface data
444      LOGICAL :: ldeallocate ! Deallocate the updated data of insertion
445      INTEGER,INTENT(in) :: kumout      ! Output unit
446     
447      !!* Local variables
448      INTEGER :: ji
449      INTEGER :: jj
450      INTEGER :: jk
451
452      ! Copy data from surf to old surf
453
454      DO ji = 1, surf%nsurf
455
456         jj=surf%nsind(ji)
457
458         oldsurf%mi(jj)    = surf%mi(ji)
459         oldsurf%mj(jj)    = surf%mj(ji)
460         oldsurf%mt(jj)    = surf%mt(ji)
461         oldsurf%nsidx(jj) = surf%nsidx(ji)
462         oldsurf%nsfil(jj) = surf%nsfil(ji)
463         oldsurf%nyea(jj)  = surf%nyea(ji)
464         oldsurf%nmon(jj)  = surf%nmon(ji)
465         oldsurf%nday(jj)  = surf%nday(ji)
466         oldsurf%nhou(jj)  = surf%nhou(ji)
467         oldsurf%nmin(jj)  = surf%nmin(ji)
468         oldsurf%mstp(jj)  = surf%mstp(ji)
469         oldsurf%nqc(jj)   = surf%nqc(ji)
470         oldsurf%ntyp(jj)  = surf%ntyp(ji)
471         oldsurf%cwmo(jj)  = surf%cwmo(ji)
472         oldsurf%rlam(jj)  = surf%rlam(ji)
473         oldsurf%rphi(jj)  = surf%rphi(ji)
474
475      END DO
476
477      DO jk = 1, surf%nvar
478
479         DO ji = 1, surf%nsurf
480           
481            jj=surf%nsind(ji)
482
483            oldsurf%robs(jj,jk)  = surf%robs(ji,jk)
484            oldsurf%rmod(jj,jk)  = surf%rmod(ji,jk)
485
486         END DO
487
488      END DO
489
490      DO jk = 1, surf%nextra
491
492         DO ji = 1, surf%nsurf
493           
494            jj=surf%nsind(ji)
495
496            oldsurf%rext(jj,jk)  = surf%rext(ji,jk)
497
498         END DO
499
500      END DO
501
502      ! Optionally deallocate the updated surface data
503
504      IF ( ldeallocate ) CALL obs_surf_dealloc( surf )
505     
506   END SUBROUTINE obs_surf_decompress
507   
508END MODULE obs_surf_def
509
Note: See TracBrowser for help on using the repository browser.