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

source: branches/dev_1784_OBS/NEMO/OPA_SRC/OBS/obs_profiles_def.F90 @ 2001

Last change on this file since 2001 was 2001, checked in by djlea, 14 years ago

Adding observation operator code

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