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_profiles_def.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_profiles_def.F90 @ 2412

Last change on this file since 2412 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

  • Property svn:keywords set to Id
File size: 30.9 KB
Line 
1MODULE obs_profiles_def
2   !!=====================================================================
3   !!                       ***  MODULE  obs_profiles_def  ***
4   !! Observation diagnostics: Storage handling for T,S profiles
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_prof            : F90 type containing the profile information
13   !!   obs_prof_var        : F90 type containing the variable definition
14   !!   obs_prof_valid       : F90 type containing the valid obs. definition
15   !!   obs_prof_alloc      : Allocates profile arrays
16   !!   obs_prof_dealloc    : Deallocates profile arrays
17   !!   obs_prof_compress   : Extract sub-information from a obs_prof type
18   !!                         to a new obs_prof type
19   !!   obs_prof_decompress : Reinsert sub-information from a obs_prof type
20   !!                         into the original obs_prof type
21   !!   obs_prof_staend     : Set npvsta and npvend of a variable within an
22   !!                         obs_prof_var type
23   !!----------------------------------------------------------------------
24   !! * Modules used
25   USE par_kind, ONLY : & ! Precision variables
26      & wp         
27   USE in_out_manager     ! I/O manager
28   USE obs_mpp, ONLY : &  ! MPP tools
29      obs_mpp_sum_integers
30   USE obs_fbm            ! Obs feedback format
31
32   IMPLICIT NONE
33
34   !! * Routine/type accessibility
35   PRIVATE
36
37   PUBLIC &
38      & obs_prof,           &
39      & obs_prof_var,       &
40      & obs_prof_valid,     &
41      & obs_prof_alloc,     &
42      & obs_prof_alloc_var, &
43      & obs_prof_dealloc,   &
44      & obs_prof_compress,  &
45      & obs_prof_decompress,&
46      & obs_prof_staend
47
48   !! * Type definition for valid observations
49
50   TYPE obs_prof_valid
51     
52      LOGICAL, POINTER, DIMENSION(:) :: luse
53
54   END TYPE obs_prof_valid
55
56   !! * Type definition for each variable
57
58   TYPE obs_prof_var
59
60      ! Arrays with size equal to the number of observations
61
62      INTEGER, POINTER, DIMENSION(:) :: &
63         & mvk,   &       !: k-th grid coord. for interpolating to profile data
64         & nvpidx,&       !: Profile number
65         & nvlidx,&       !: Level number in profile
66         & nvqc,  &       !: Variable QC flags
67         & idqc           !: Depth QC flag
68
69      REAL(KIND=wp), POINTER, DIMENSION(:) :: &
70         & vdep,  &       !: Depth coordinate of profile data
71         & vobs,  &       !: Profile data
72         & vmod           !: Model counterpart of the profile data vector
73
74      REAL(KIND=wp), POINTER, DIMENSION(:,:) :: &
75         & vext           !: Extra variables
76
77      INTEGER, POINTER, DIMENSION(:) :: &
78         & nvind          !: Source indices of temp. data in compressed data
79
80      ! Arrays with size equal to idefnqcf times the number of observations
81      INTEGER, POINTER, DIMENSION(:,:) :: &
82         & idqcf,  &      !: Depth QC flags
83         & nvqcf          !: Variable QC flags
84
85   END TYPE obs_prof_var
86
87   !! * Type definition for profile observation type
88
89   TYPE obs_prof
90
91      ! Bookkeeping
92
93      INTEGER :: nvar     !: Number of variables
94      INTEGER :: next     !: Number of extra fields
95      INTEGER :: nprof    !: Total number of profiles within window.
96      INTEGER :: nstp     !: Number of time steps
97      INTEGER :: npi      !: Number of 3D grid points
98      INTEGER :: npj
99      INTEGER :: npk
100      INTEGER :: nprofup  !: Observation counter used in obs_oper
101
102      ! Bookkeeping arrays with sizes equal to number of variables
103
104      INTEGER, POINTER, DIMENSION(:) :: &
105         & nvprot,   &    !: Local total number of profile T data
106         & nvprotmpp      !: Global total number of profile T data
107     
108      ! Arrays with size equal to the number of profiles
109
110      INTEGER, POINTER, DIMENSION(:) :: &
111         & npidx,&        !: Profile number
112         & npfil,&        !: Profile number in file
113         & nyea, &        !: Year of profile
114         & nmon, &        !: Month of profile
115         & nday, &        !: Day of profile
116         & nhou, &        !: Hour of profile
117         & nmin, &        !: Minute of profile
118         & mstp, &        !: Time step nearest to profile
119         & nqc,  &        !: Profile QC
120         & ntyp, &        !: Type of profile product (WMO table 1770)
121         & ipqc, &        !: Position QC
122         & itqc           !: Time QC
123
124      REAL(KIND=wp), POINTER, DIMENSION(:) :: &
125         & rlam, &        !: Longitude coordinate of profile data
126         & rphi           !: Latitude coordinate of profile data
127
128      CHARACTER(LEN=8), POINTER, DIMENSION(:) :: &
129         & cwmo           !: Profile WMO indentifier
130     
131      ! Arrays with size equal to the number of profiles times
132      ! number of variables
133
134      INTEGER, POINTER, DIMENSION(:,:) :: &
135         & npvsta, &      !: Start of each variable profile in full arrays
136         & npvend, &      !: End of each variable profile in full arrays
137         & mi,     &      !: i-th grid coord. for interpolating to profile T data
138         & mj,     &      !: j-th grid coord. for interpolating to profile T data
139         & ivqc           !: QC flags for all levels for a variable
140
141      ! Arrays with size equal to idefnqcf
142      ! the number of profiles times number of variables
143      INTEGER, POINTER, DIMENSION(:,:) :: &
144         & nqcf,  &       !: Observation QC flags
145         & ipqcf, &       !: Position QC flags
146         & itqcf          !: Time QC flags
147
148      ! Arrays with size equal to idefnqcf
149      ! the number of profiles times number of variables
150      INTEGER, POINTER, DIMENSION(:,:,:) :: &
151         & ivqcf
152
153      ! Arrays of variables
154
155      TYPE(obs_prof_var), POINTER, DIMENSION(:) :: var
156
157      ! Arrays with size equal to the number of time steps in the window
158
159      INTEGER, POINTER, DIMENSION(:) :: &
160         & npstp,    &    !: Total number of profiles
161         & npstpmpp       !: Total number of profiles
162
163      ! Arrays with size equal to the number of time steps in the window times
164      ! number of variables
165
166      INTEGER, POINTER, DIMENSION(:,:) :: &
167         & nvstp,    &    !: Local total num. of profile data each time step
168         & nvstpmpp       !: Global total num. of profile data each time step
169     
170      ! Arrays with size equal to the number of grid points times number of
171      ! variables
172
173      REAL(KIND=wp), POINTER, DIMENSION(:,:,:,:) :: &
174         & vdmean        !: Daily averaged model field
175
176      ! Arrays used to store source indices when
177      ! compressing obs_prof derived types
178     
179      ! Array with size nprof
180
181      INTEGER, POINTER, DIMENSION(:) :: &
182         & npind         !: Source indices of profile data in compressed data
183
184   END TYPE obs_prof
185
186   !!----------------------------------------------------------------------
187   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
188   !! $Id$
189   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
190   !!----------------------------------------------------------------------
191
192CONTAINS
193   
194   SUBROUTINE obs_prof_alloc( prof,  kvar, kext, kprof,  &
195      &                       ko3dt, kstp, kpi, kpj, kpk )
196      !!----------------------------------------------------------------------
197      !!                     ***  ROUTINE obs_prof_alloc  ***
198      !!                     
199      !! ** Purpose : - Allocate data for profile arrays
200      !!
201      !! ** Method  : - Fortran-90 dynamic arrays
202      !!
203      !! History :
204      !!        !  07-01  (K. Mogensen) Original code
205      !!        !  07-03  (K. Mogensen) Generalized profiles
206      !!----------------------------------------------------------------------
207      !! * Arguments
208      TYPE(obs_prof), INTENT(INOUT) :: prof      ! Profile data to be allocated
209      INTEGER, INTENT(IN) :: kprof  ! Number of profiles
210      INTEGER, INTENT(IN) :: kvar   ! Number of variables
211      INTEGER, INTENT(IN) :: kext   ! Number of extra fields within each variable
212      INTEGER, INTENT(IN), DIMENSION(kvar) :: &
213         & ko3dt     ! Number of observations per variables
214      INTEGER, INTENT(IN) :: kstp   ! Number of time steps
215      INTEGER, INTENT(IN) :: kpi    ! Number of 3D grid points
216      INTEGER, INTENT(IN) :: kpj
217      INTEGER, INTENT(IN) :: kpk
218
219      !!* Local variables
220      INTEGER :: jvar
221      INTEGER :: ji
222
223      ! Set bookkeeping variables
224
225      prof%nvar      = kvar
226      prof%next      = kext
227      prof%nprof     = kprof
228
229      prof%nstp      = kstp
230      prof%npi       = kpi
231      prof%npj       = kpj
232      prof%npk       = kpk
233
234      ! Allocate arrays of size number of variables
235
236      ALLOCATE( &
237         & prof%nvprot(kvar),   &
238         & prof%nvprotmpp(kvar) &
239         )
240         
241      DO jvar = 1, kvar
242         prof%nvprot   (jvar) = ko3dt(jvar)
243         prof%nvprotmpp(jvar) = 0
244      END DO
245
246      ! Allocate arrays of size number of profiles
247      ! times number of variables
248     
249      ALLOCATE( &
250         & prof%npvsta(kprof,kvar), & 
251         & prof%npvend(kprof,kvar), &
252         & prof%mi(kprof,kvar),     &
253         & prof%mj(kprof,kvar),     &
254         & prof%ivqc(kprof,kvar)    &
255         )
256
257      ! Allocate arrays of size iqcfdef times number of profiles
258      ! times number of variables
259
260      ALLOCATE( &
261         & prof%ivqcf(idefnqcf,kprof,kvar) &
262         & )
263
264      ! Allocate arrays of size number of profiles
265
266      ALLOCATE( &
267         & prof%npidx(kprof),   &
268         & prof%npfil(kprof),   &
269         & prof%nyea(kprof),    &
270         & prof%nmon(kprof),    &
271         & prof%nday(kprof),    &
272         & prof%nhou(kprof),    &
273         & prof%nmin(kprof),    &
274         & prof%mstp(kprof),    &
275         & prof%nqc(kprof),     &
276         & prof%ipqc(kprof),    &
277         & prof%itqc(kprof),    &
278         & prof%ntyp(kprof),    &
279         & prof%rlam(kprof),    &
280         & prof%rphi(kprof),    &
281         & prof%cwmo(kprof),    &
282         & prof%npind(kprof)    &
283         & )
284
285      ! Allocate arrays of size idefnqcf times number of profiles
286
287      ALLOCATE( &
288         & prof%nqcf(idefnqcf,kprof),  &
289         & prof%ipqcf(idefnqcf,kprof), &
290         & prof%itqcf(idefnqcf,kprof)  &
291         & )
292
293      ! Allocate obs_prof_var type
294      ALLOCATE( &
295         & prof%var(kvar) &
296         & )
297
298      ! For each variables allocate arrays of size number of observations
299
300      DO jvar = 1, kvar
301
302         IF ( ko3dt(jvar) >= 0 ) THEN
303            CALL obs_prof_alloc_var( prof, jvar, kext, ko3dt(jvar) )
304         ENDIF
305         
306      END DO
307
308      ! Allocate arrays of size number of time step size
309
310      ALLOCATE( &
311         & prof%npstp(kstp),   &
312         & prof%npstpmpp(kstp) &
313         & )
314
315      ! Allocate arrays of size number of time step size times
316      ! number of variables
317     
318      ALLOCATE( &
319         & prof%nvstp(kstp,kvar),   &
320         & prof%nvstpmpp(kstp,kvar) &
321         & )
322
323      ! Allocate arrays of size number of grid points size times
324      ! number of variables
325
326      ALLOCATE( &
327         & prof%vdmean(kpi,kpj,kpk,kvar) &
328         & )
329
330      ! Set defaults for compression indices
331     
332      DO ji = 1, kprof
333         prof%npind(ji) = ji
334      END DO
335
336      DO jvar = 1, kvar
337         DO ji = 1, ko3dt(jvar)
338            prof%var(jvar)%nvind(ji) = ji
339         END DO
340      END DO
341
342      ! Set defaults for number of observations per time step
343
344      prof%npstp(:)      = 0
345      prof%npstpmpp(:)   = 0
346      prof%nvstp(:,:)    = 0
347      prof%nvstpmpp(:,:) = 0
348     
349      ! Set the observation counter used in obs_oper
350
351      prof%nprofup     = 0
352
353   END SUBROUTINE obs_prof_alloc
354
355   SUBROUTINE obs_prof_dealloc( prof )
356      !!----------------------------------------------------------------------
357      !!                     ***  ROUTINE obs_prof_dealloc  ***
358      !!                     
359      !! ** Purpose : - Deallocate data for profile arrays
360      !!
361      !! ** Method  : - Fortran-90 dynamic arrays
362      !!
363      !! History :
364      !!        !  07-01  (K. Mogensen) Original code
365      !!----------------------------------------------------------------------
366      !! * Arguments
367      TYPE(obs_prof), INTENT(INOUT) :: &
368         & prof      ! Profile data to be deallocated
369
370      !!* Local variables
371      INTEGER :: &
372         & jvar
373
374      ! Deallocate arrays of size number of profiles
375      ! times number of variables
376     
377      DEALLOCATE( &
378         & prof%npvsta, & 
379         & prof%npvend  &
380         )
381
382      ! Dellocate arrays of size number of profiles size
383
384      DEALLOCATE( &
385         & prof%mi,      &
386         & prof%mj,      &
387         & prof%ivqc,    &
388         & prof%ivqcf,   &
389         & prof%npidx,   &
390         & prof%npfil,   &
391         & prof%nyea,    &
392         & prof%nmon,    &
393         & prof%nday,    &
394         & prof%nhou,    &
395         & prof%nmin,    &
396         & prof%mstp,    &
397         & prof%nqc,     &
398         & prof%ipqc,    &
399         & prof%itqc,    &
400         & prof%nqcf,    &
401         & prof%ipqcf,   &
402         & prof%itqcf,   &
403         & prof%ntyp,    &
404         & prof%rlam,    &
405         & prof%rphi,    &
406         & prof%cwmo,    &
407         & prof%npind    &
408         & )
409
410      ! For each variables allocate arrays of size number of observations
411
412      DO jvar = 1, prof%nvar
413
414         IF ( prof%nvprot(jvar) >= 0 ) THEN
415
416            CALL obs_prof_dealloc_var( prof, jvar )
417
418         ENDIF
419         
420      END DO
421
422      ! Dellocate obs_prof_var type
423      DEALLOCATE( &
424         & prof%var &
425         & )
426
427      ! Deallocate arrays of size number of time step size
428
429      DEALLOCATE( &
430         & prof%npstp,   &
431         & prof%npstpmpp &
432         & )
433
434      ! Deallocate arrays of size number of time step size times
435      ! number of variables
436     
437      DEALLOCATE( &
438         & prof%nvstp,   &
439         & prof%nvstpmpp &
440         & )
441
442      ! Deallocate arrays of size number of grid points size times
443      ! number of variables
444
445      DEALLOCATE( &
446         & prof%vdmean &
447         & )
448
449      ! Dellocate arrays of size number of variables
450
451      DEALLOCATE( &
452         & prof%nvprot,  &
453         & prof%nvprotmpp &
454         )
455
456
457   END SUBROUTINE obs_prof_dealloc
458
459
460   SUBROUTINE obs_prof_alloc_var( prof, kvar, kext, kobs )
461
462      !!----------------------------------------------------------------------
463      !!                     ***  ROUTINE obs_prof_alloc_var  ***
464      !!                     
465      !! ** Purpose : - Allocate data for variable data in profile arrays
466      !!
467      !! ** Method  : - Fortran-90 dynamic arrays
468      !!
469      !! History :
470      !!        !  07-03  (K. Mogensen) Original code
471      !! * Arguments
472      TYPE(obs_prof), INTENT(INOUT) :: prof   ! Profile data to be allocated
473      INTEGER, INTENT(IN) :: kvar   ! Variable number
474      INTEGER, INTENT(IN) :: kext   ! Number of extra fields within each variable
475      INTEGER, INTENT(IN) :: kobs   ! Number of observations
476     
477      ALLOCATE( & 
478         & prof%var(kvar)%mvk(kobs),       &
479         & prof%var(kvar)%nvpidx(kobs),    &
480         & prof%var(kvar)%nvlidx(kobs),    &
481         & prof%var(kvar)%nvqc(kobs),      &
482         & prof%var(kvar)%idqc(kobs),      &
483         & prof%var(kvar)%vdep(kobs),      &
484         & prof%var(kvar)%vobs(kobs),      &
485         & prof%var(kvar)%vmod(kobs),      &
486         & prof%var(kvar)%nvind(kobs)      &
487         & )
488      ALLOCATE( & 
489         & prof%var(kvar)%idqcf(idefnqcf,kobs), &
490         & prof%var(kvar)%nvqcf(idefnqcf,kobs)  &
491         & )
492      IF (kext>0) THEN
493         ALLOCATE( & 
494            & prof%var(kvar)%vext(kobs,kext) &
495            & )
496      ENDIF
497
498   END SUBROUTINE obs_prof_alloc_var
499
500   SUBROUTINE obs_prof_dealloc_var( prof, kvar )
501
502      !!----------------------------------------------------------------------
503      !!                     ***  ROUTINE obs_prof_alloc_var  ***
504      !!                     
505      !! ** Purpose : - Allocate data for variable data in profile arrays
506      !!
507      !! ** Method  : - Fortran-90 dynamic arrays
508      !!
509      !! History :
510      !!        !  07-03  (K. Mogensen) Original code
511      !! * Arguments
512      TYPE(obs_prof), INTENT(INOUT) :: prof   ! Profile data to be allocated
513      INTEGER, INTENT(IN) :: kvar      ! Variable number
514     
515      DEALLOCATE( & 
516         & prof%var(kvar)%mvk,    &
517         & prof%var(kvar)%nvpidx, &
518         & prof%var(kvar)%nvlidx, &
519         & prof%var(kvar)%nvqc,   &
520         & prof%var(kvar)%idqc,   &
521         & prof%var(kvar)%vdep,   &
522         & prof%var(kvar)%vobs,   &
523         & prof%var(kvar)%vmod,   &
524         & prof%var(kvar)%nvind,  &
525         & prof%var(kvar)%idqcf,  &
526         & prof%var(kvar)%nvqcf   &
527         & )
528      IF (prof%next>0) THEN
529         DEALLOCATE( & 
530            & prof%var(kvar)%vext  &
531            & )
532      ENDIF
533
534   END SUBROUTINE obs_prof_dealloc_var
535
536   SUBROUTINE obs_prof_compress( prof,   newprof, lallocate, &
537      &                          kumout, lvalid,   lvvalid )
538      !!----------------------------------------------------------------------
539      !!                     ***  ROUTINE obs_prof_compress  ***
540      !!                     
541      !! ** Purpose : - Extract sub-information from a obs_prof type
542      !!                into a new obs_prof type
543      !!
544      !! ** Method  : - The data is copied from prof to new prof.
545      !!                In the case of lvalid and lvvalid both being
546      !!                present only the selected data will be copied.
547      !!                If lallocate is true the data in the newprof is
548      !!                allocated either with the same number of elements
549      !!                as prof or with only the subset of elements defined
550      !!                by the optional selection in lvalid and lvvalid
551      !!
552      !! History :
553      !!        !  07-01  (K. Mogensen) Original code
554      !!----------------------------------------------------------------------
555      !! * Arguments
556      TYPE(obs_prof), INTENT(IN)    :: prof      ! Original profile
557      TYPE(obs_prof), INTENT(INOUT) :: newprof   ! New profile with the copy of the data
558      LOGICAL :: lallocate                ! Allocate newprof data
559      INTEGER,INTENT(IN) :: kumout        ! Fortran unit for messages
560      TYPE(obs_prof_valid), OPTIONAL, INTENT(in) :: &
561         & lvalid        ! Valid profiles
562      TYPE(obs_prof_valid), OPTIONAL, INTENT(in), DIMENSION(prof%nvar) :: &
563         & lvvalid       ! Valid data within the profiles
564     
565      !!* Local variables
566      INTEGER :: inprof
567      INTEGER, DIMENSION(prof%nvar) :: &
568         & invpro
569      INTEGER :: jvar
570      INTEGER :: jext
571      INTEGER :: ji
572      INTEGER :: jj 
573      LOGICAL :: lfirst
574      TYPE(obs_prof_valid) :: &
575         & llvalid
576      TYPE(obs_prof_valid), DIMENSION(prof%nvar) :: &
577         & llvvalid
578      LOGICAL :: lallpresent
579      LOGICAL :: lnonepresent
580
581      ! Check that either all or none of the masks are persent.
582
583      lallpresent  = .FALSE.
584      lnonepresent = .FALSE.
585      IF ( PRESENT(lvalid) .AND. PRESENT(lvvalid) ) THEN
586         lallpresent =  .TRUE.
587      ELSEIF ( ( .NOT. PRESENT(lvalid)  ) .AND. &
588         &     ( .NOT. PRESENT(lvvalid) ) ) THEN
589         lnonepresent = .TRUE.
590      ELSE
591         CALL ctl_stop('Error in obs_prof_compress:', &
592            &          'Either all selection variables should be set', &
593            &          'or no selection variable should be set' )
594      ENDIF
595     
596      ! Count how many elements there should be in the new data structure
597
598      IF ( lallpresent ) THEN
599         inprof = 0
600         invpro(:) = 0
601         DO ji = 1, prof%nprof
602            IF ( lvalid%luse(ji) ) THEN
603               inprof=inprof+1
604               DO jvar = 1, prof%nvar
605                  DO jj = prof%npvsta(ji,jvar), prof%npvend(ji,jvar)
606                     IF ( lvvalid(jvar)%luse(jj) ) &
607                        &           invpro(jvar) = invpro(jvar) +1
608                  END DO
609               END DO
610            ENDIF
611         END DO
612      ELSE
613         inprof    = prof%nprof
614         invpro(:) = prof%nvprot(:)
615      ENDIF
616
617      ! Optionally allocate data in the new data structure
618
619      IF ( lallocate ) THEN
620         CALL obs_prof_alloc( newprof,   prof%nvar, &
621            &                 prof%next,            &
622            &                 inprof,    invpro,    &
623            &                 prof%nstp, prof%npi,  &
624            &                 prof%npj,  prof%npk )
625      ENDIF
626
627      ! Allocate temporary mask array to unify the code for both cases
628
629      ALLOCATE( llvalid%luse(prof%nprof) )
630      DO jvar = 1, prof%nvar
631         ALLOCATE( llvvalid(jvar)%luse(prof%nvprot(jvar)) )
632      END DO
633      IF ( lallpresent ) THEN
634         llvalid%luse(:) = lvalid%luse(:)
635         DO jvar = 1, prof%nvar
636            llvvalid(jvar)%luse(:) = lvvalid(jvar)%luse(:)
637         END DO
638      ELSE
639         llvalid%luse(:) = .TRUE.
640         DO jvar = 1, prof%nvar
641            llvvalid(jvar)%luse(:) = .TRUE.
642         END DO
643      ENDIF
644
645      ! Setup bookkeeping variables
646
647      inprof    = 0
648      invpro(:) = 0
649
650      newprof%npvsta(:,:) =  0
651      newprof%npvend(:,:) = -1
652     
653      ! Loop over source profiles
654
655      DO ji = 1, prof%nprof
656
657         IF ( llvalid%luse(ji) ) THEN
658
659            ! Copy the header information
660
661            inprof = inprof + 1
662
663            newprof%mi(inprof,:)  = prof%mi(ji,:)
664            newprof%mj(inprof,:) = prof%mj(ji,:)
665            newprof%npidx(inprof) = prof%npidx(ji)
666            newprof%npfil(inprof) = prof%npfil(ji)
667            newprof%nyea(inprof)  = prof%nyea(ji)
668            newprof%nmon(inprof)  = prof%nmon(ji)
669            newprof%nday(inprof)  = prof%nday(ji)
670            newprof%nhou(inprof)  = prof%nhou(ji)
671            newprof%nmin(inprof)  = prof%nmin(ji)
672            newprof%mstp(inprof)  = prof%mstp(ji)
673            newprof%nqc(inprof)   = prof%nqc(ji)
674            newprof%ipqc(inprof)  = prof%ipqc(ji)
675            newprof%itqc(inprof)  = prof%itqc(ji)
676            newprof%ivqc(inprof,:)= prof%ivqc(ji,:)
677            newprof%ntyp(inprof)  = prof%ntyp(ji)
678            newprof%rlam(inprof)  = prof%rlam(ji)
679            newprof%rphi(inprof)  = prof%rphi(ji)
680            newprof%cwmo(inprof)  = prof%cwmo(ji)
681           
682            ! QC info
683
684            newprof%nqcf(:,inprof)    = prof%nqcf(:,ji)
685            newprof%ipqcf(:,inprof)   = prof%ipqcf(:,ji)
686            newprof%itqcf(:,inprof)   = prof%itqcf(:,ji)
687            newprof%ivqcf(:,inprof,:) = prof%ivqcf(:,ji,:)
688           
689            ! npind is the index of the original profile
690           
691            newprof%npind(inprof) = ji
692
693            ! Copy the variable information
694
695            DO jvar = 1, prof%nvar
696
697               lfirst = .TRUE.
698               
699               DO jj = prof%npvsta(ji,jvar), prof%npvend(ji,jvar)
700                 
701                  IF ( llvvalid(jvar)%luse(jj) ) THEN
702
703                     invpro(jvar) = invpro(jvar) + 1
704                 
705                     ! Book keeping information
706                                   
707                     IF ( lfirst ) THEN
708                        lfirst = .FALSE.
709                        newprof%npvsta(inprof,jvar) = invpro(jvar)
710                     ENDIF
711                     newprof%npvend(inprof,jvar) = invpro(jvar)
712
713                     ! Variable data
714                     
715                     newprof%var(jvar)%mvk(invpro(jvar))    = &
716                        &                           prof%var(jvar)%mvk(jj)
717                     newprof%var(jvar)%nvpidx(invpro(jvar)) = &
718                        &                           prof%var(jvar)%nvpidx(jj)
719                     newprof%var(jvar)%nvlidx(invpro(jvar)) = &
720                        &                           prof%var(jvar)%nvlidx(jj)
721                     newprof%var(jvar)%nvqc(invpro(jvar))   = &
722                        &                           prof%var(jvar)%nvqc(jj)
723                     newprof%var(jvar)%idqc(invpro(jvar))   = &
724                        &                           prof%var(jvar)%idqc(jj)
725                     newprof%var(jvar)%idqcf(:,invpro(jvar))= &
726                        &                           prof%var(jvar)%idqcf(:,jj)
727                     newprof%var(jvar)%nvqcf(:,invpro(jvar))= &
728                        &                           prof%var(jvar)%nvqcf(:,jj)
729                     newprof%var(jvar)%vdep(invpro(jvar))   = &
730                        &                           prof%var(jvar)%vdep(jj)
731                     newprof%var(jvar)%vobs(invpro(jvar))   = &
732                        &                           prof%var(jvar)%vobs(jj)
733                     newprof%var(jvar)%vmod(invpro(jvar))   = &
734                        &                           prof%var(jvar)%vmod(jj)
735                     DO jext = 1, prof%next
736                        newprof%var(jvar)%vext(invpro(jvar),jext) = &
737                           &                      prof%var(jvar)%vext(jj,jext)
738                     END DO
739                 
740                     ! nvind is the index of the original variable data
741                     
742                     newprof%var(jvar)%nvind(invpro(jvar))  = jj
743                     
744                  ENDIF
745
746               END DO
747
748            END DO
749
750         ENDIF
751
752      END DO
753
754      ! Update MPP counters
755
756      DO jvar = 1, prof%nvar
757         newprof%nvprot(jvar) = invpro(jvar)
758      END DO
759      CALL obs_mpp_sum_integers ( newprof%nvprot, newprof%nvprotmpp,&
760         &                        prof%nvar )
761     
762      ! Set book keeping variables which do not depend on number of obs.
763
764      newprof%nvar     = prof%nvar
765      newprof%next     = prof%next
766      newprof%nstp     = prof%nstp
767      newprof%npi      = prof%npi
768      newprof%npj      = prof%npj
769      newprof%npk      = prof%npk
770 
771      ! Deallocate temporary data
772
773      DO jvar = 1, prof%nvar
774         DEALLOCATE( llvvalid(jvar)%luse )
775      END DO
776 
777      DEALLOCATE( llvalid%luse )
778     
779   END SUBROUTINE obs_prof_compress
780
781   SUBROUTINE obs_prof_decompress( prof, oldprof, ldeallocate, kumout )
782      !!----------------------------------------------------------------------
783      !!                     ***  ROUTINE obs_prof_decompress  ***
784      !!                     
785      !! ** Purpose : - Copy back information to original profile type
786      !!
787      !! ** Method  : - Reinsert updated information from a previous
788      !!                copied/compressed profile type into the original
789      !!                profile data and optionally deallocate the prof
790      !!                data input
791      !!
792      !! History :
793      !!        !  07-01  (K. Mogensen) Original code
794      !!----------------------------------------------------------------------
795      !! * Arguments
796      TYPE(obs_prof),INTENT(INOUT) :: prof      ! Updated profile data
797      TYPE(obs_prof),INTENT(INOUT) :: oldprof   ! Original profile data
798      LOGICAL :: ldeallocate         ! Deallocate the updated data of insertion
799      INTEGER,INTENT(in) :: kumout   ! Output unit
800     
801      !!* Local variables
802      INTEGER :: jvar
803      INTEGER :: jext
804      INTEGER :: ji
805      INTEGER :: jj
806      INTEGER :: jk
807      INTEGER :: jl
808
809      DO ji = 1, prof%nprof
810
811         ! Copy header information
812         
813         jk = prof%npind(ji)
814     
815         oldprof%mi(jk,:)  = prof%mi(ji,:)
816         oldprof%mj(jk,:)  = prof%mj(ji,:)
817         oldprof%npidx(jk) = prof%npidx(ji)
818         oldprof%npfil(jk) = prof%npfil(ji)
819         oldprof%nyea(jk)  = prof%nyea(ji)
820         oldprof%nmon(jk)  = prof%nmon(ji)
821         oldprof%nday(jk)  = prof%nday(ji)
822         oldprof%nhou(jk)  = prof%nhou(ji)
823         oldprof%nmin(jk)  = prof%nmin(ji)
824         oldprof%mstp(jk)  = prof%mstp(ji)
825         oldprof%nqc(jk)   = prof%nqc(ji)
826         oldprof%ipqc(jk)  = prof%ipqc(ji)
827         oldprof%itqc(jk)  = prof%itqc(ji)
828         oldprof%ivqc(jk,:)= prof%ivqc(ji,:)
829         oldprof%ntyp(jk)  = prof%ntyp(ji)
830         oldprof%rlam(jk)  = prof%rlam(ji)
831         oldprof%rphi(jk)  = prof%rphi(ji)
832         oldprof%cwmo(jk)  = prof%cwmo(ji)
833         
834         ! QC info
835
836         oldprof%nqcf(:,jk)    = prof%nqcf(:,ji)
837         oldprof%ipqcf(:,jk)   = prof%ipqcf(:,ji)
838         oldprof%itqcf(:,jk)   = prof%itqcf(:,ji)
839         oldprof%ivqcf(:,jk,:) = prof%ivqcf(:,ji,:)
840
841         ! Copy the variable information
842
843         DO jvar = 1, prof%nvar
844
845            DO jj = prof%npvsta(ji,jvar), prof%npvend(ji,jvar)
846               
847               jl = prof%var(jvar)%nvind(jj)
848
849               oldprof%var(jvar)%mvk(jl)    = prof%var(jvar)%mvk(jj)
850               oldprof%var(jvar)%nvpidx(jl) = prof%var(jvar)%nvpidx(jj)
851               oldprof%var(jvar)%nvlidx(jl) = prof%var(jvar)%nvlidx(jj)
852               oldprof%var(jvar)%nvqc(jl)   = prof%var(jvar)%nvqc(jj)
853               oldprof%var(jvar)%idqc(jl)   = prof%var(jvar)%idqc(jj)
854               oldprof%var(jvar)%vdep(jl)   = prof%var(jvar)%vdep(jj)
855               oldprof%var(jvar)%vobs(jl)   = prof%var(jvar)%vobs(jj)
856               oldprof%var(jvar)%vmod(jl)   = prof%var(jvar)%vmod(jj)
857               oldprof%var(jvar)%idqcf(:,jl) = prof%var(jvar)%idqcf(:,jj)
858               oldprof%var(jvar)%nvqcf(:,jl) = prof%var(jvar)%nvqcf(:,jj)
859               DO jext = 1, prof%next
860                  oldprof%var(jvar)%vext(jl,jext) = &
861                     &                        prof%var(jvar)%vext(jj,jext)
862               END DO
863               
864            END DO
865
866         END DO
867         
868      END DO
869
870      ! Optionally deallocate the updated profile data
871
872      IF ( ldeallocate ) CALL obs_prof_dealloc( prof )
873     
874   END SUBROUTINE obs_prof_decompress
875
876   SUBROUTINE obs_prof_staend( prof, kvarno )
877      !!----------------------------------------------------------------------
878      !!                     ***  ROUTINE obs_prof_decompress  ***
879      !!                     
880      !! ** Purpose : - Set npvsta and npvend of a variable within
881      !!                an obs_prof_var type
882      !!
883      !! ** Method  : - Find the start and stop of a profile by searching
884      !!                through the data
885      !!
886      !! History :
887      !!        !  07-04  (K. Mogensen) Original code
888      !!----------------------------------------------------------------------
889      !! * Arguments
890      TYPE(obs_prof),INTENT(INOUT) :: prof     ! Profile data
891      INTEGER,INTENT(IN) :: kvarno     ! Variable number
892
893      !!* Local variables
894      INTEGER :: ji
895      INTEGER :: iprofno
896
897      !-----------------------------------------------------------------------
898      ! Compute start and end bookkeeping arrays
899      !-----------------------------------------------------------------------
900
901      prof%npvsta(:,kvarno) = prof%nvprot(kvarno) + 1
902      prof%npvend(:,kvarno) = -1
903      DO ji = 1, prof%nvprot(kvarno)
904         iprofno = prof%var(kvarno)%nvpidx(ji)
905         prof%npvsta(iprofno,kvarno) = &
906            & MIN( ji, prof%npvsta(iprofno,kvarno) )
907         prof%npvend(iprofno,kvarno) = &
908            & MAX( ji, prof%npvend(iprofno,kvarno) )
909      END DO
910
911      DO ji = 1, prof%nprof
912         IF ( prof%npvsta(ji,kvarno) == ( prof%nvprot(kvarno) + 1 ) ) &
913            & prof%npvsta(ji,kvarno) = 0
914      END DO
915
916   END SUBROUTINE obs_prof_staend
917   
918END MODULE obs_profiles_def
919
Note: See TracBrowser for help on using the repository browser.