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_r5518_obs_oper_update_vel_obsoper/NEMOGCM/NEMO/OPA_SRC/OBS – NEMO

source: branches/UKMO/dev_r5518_obs_oper_update_vel_obsoper/NEMOGCM/NEMO/OPA_SRC/OBS/obs_surf_def.F90 @ 13384

Last change on this file since 13384 was 13384, checked in by mattmartin, 4 years ago

First working version of surface velocity observation operator code.

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