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.
Changeset 9308 – NEMO

Changeset 9308


Ignore:
Timestamp:
2018-02-06T11:30:42+01:00 (6 years ago)
Author:
kingr
Message:

Merging changes required to read and write instrument error from/to fdbk file (e.g., SST_STD).

Location:
branches/UKMO/dev_r5518_obs_oper_update/NEMOGCM/NEMO/OPA_SRC/OBS
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_obs_oper_update/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_surf.F90

    r7992 r9308  
    9797      INTEGER :: ios 
    9898      INTEGER :: ioserrcount 
     99      INTEGER :: iextr 
    99100      INTEGER, PARAMETER :: jpsurfmaxtype = 1024 
    100101      INTEGER, DIMENSION(knumfiles) :: irefdate 
     
    108109         & iindx,    & 
    109110         & ifileidx, & 
    110          & isurfidx 
     111         & isurfidx, & 
     112         & iadd_std 
    111113      REAL(wp), DIMENSION(:), ALLOCATABLE :: & 
    112114         & zphi, & 
     
    122124 
    123125      ! Local initialization 
    124       iobs = 0 
    125  
     126      iobs  = 0 
     127      iextr = kextr 
    126128      !----------------------------------------------------------------------- 
    127129      ! Count the number of files needed and allocate the obfbdata type 
     
    131133 
    132134      ALLOCATE( inpfiles(inobf) ) 
     135      ALLOCATE( iadd_std(inobf) ) 
    133136 
    134137      surf_files : DO jj = 1, inobf 
     
    195198                  ENDIF 
    196199               END DO 
     200            ENDIF 
     201 
     202            iadd_std(jj) = -1 
     203            IF ( inpfiles(jj)%nadd > 0 ) THEN 
     204               DO ji = 1, inpfiles(jj)%nadd 
     205                  IF ( TRIM( inpfiles(jj)%caddname(ji) ) == 'STD' ) THEN 
     206                     iextr = kextr + 1 
     207                     iadd_std(jj) = ji 
     208                  ENDIF 
     209               END DO 
     210            ENDIF 
     211 
     212            IF(lwp) THEN 
     213               IF ( iadd_std(jj) /= -1 ) THEN 
     214                  WRITE(numout,*) ' STD variable available in input file so passing it through the obs oper' 
     215                  WRITE(numout,*) 
     216               ENDIF 
    197217            ENDIF 
    198218 
     
    339359         &               iindx   ) 
    340360 
    341       CALL obs_surf_alloc( surfdata, iobs, kvars, kextr, kstp, jpi, jpj ) 
     361      CALL obs_surf_alloc( surfdata, iobs, kvars, iextr, kstp, jpi, jpj ) 
    342362 
    343363      ! Read obs/positions, QC, all variable and assign to surfdata 
     
    345365      iobs = 0 
    346366      surfdata%cvars(:)  = clvars(:) 
     367      IF ( ldmod .AND. ( TRIM( surfdata%cvars(1) ) == 'SLA' ) ) THEN 
     368         surfdata%cext(1) = 'SSH' 
     369         surfdata%cext(2) = 'MDT' 
     370      ENDIF 
     371      IF ( iextr > kextr ) surfdata%cext(iextr) = 'STD' 
    347372 
    348373      ityp   (:) = 0 
     
    426451               surfdata%robs(iobs,1) = inpfiles(jj)%pob(1,ji,1) 
    427452 
    428  
    429453               ! Model and MDT is set to fbrmdi unless read from file 
    430454               IF ( ldmod ) THEN 
     
    437461                  surfdata%rmod(iobs,1) = fbrmdi 
    438462                  IF ( TRIM(surfdata%cvars(1)) == 'SLA' ) surfdata%rext(iobs,:) = fbrmdi 
     463               ENDIF 
     464 
     465               ! STD (obs error standard deviation) read from file and passed through obs operator 
     466               IF ( iadd_std(jj) /= -1 ) THEN 
     467                  surfdata%rext(iobs,iextr) = inpfiles(jj)%padd(1,ji,iadd_std(jj),1) 
    439468               ENDIF 
    440469            ENDIF 
     
    488517      END DO 
    489518      DEALLOCATE( inpfiles ) 
     519      DEALLOCATE( iadd_std ) 
    490520 
    491521   END SUBROUTINE obs_rea_surf 
  • branches/UKMO/dev_r5518_obs_oper_update/NEMOGCM/NEMO/OPA_SRC/OBS/obs_surf_def.F90

    r7992 r9308  
    7171      CHARACTER(len=8), POINTER, DIMENSION(:) :: & 
    7272         & cvars          !: Variable names 
     73 
     74      CHARACTER(len=8), POINTER, DIMENSION(:) :: & 
     75         & cext           !: Extra field names 
    7376 
    7477      CHARACTER(LEN=8), POINTER, DIMENSION(:) :: & 
     
    200203 
    201204      ALLOCATE( &  
    202          & surf%rext(ksurf,kextra) & 
     205         & surf%rext(ksurf,kextra), & 
     206         & surf%cext(kextra)        & 
    203207         & ) 
    204208 
    205209      surf%rext(:,:) = 0.0_wp  
     210 
     211      DO ji = 1, kextra 
     212         surf%cext(ji) = "NotSet" 
     213      END DO 
    206214 
    207215      ! Allocate arrays of number of time step size 
     
    288296 
    289297      DEALLOCATE( &  
    290          & surf%rext & 
     298         & surf%rext, & 
     299         & surf%cext & 
    291300         & ) 
    292301 
     
    435444      newsurf%nstp     = surf%nstp 
    436445      newsurf%cvars(:) = surf%cvars(:) 
     446      newsurf%cext(:)  = surf%cext(:) 
    437447       
    438448      ! Set gridded stuff 
  • branches/UKMO/dev_r5518_obs_oper_update/NEMOGCM/NEMO/OPA_SRC/OBS/obs_write.F90

    r9306 r9308  
    418418      INTEGER :: iadd 
    419419      INTEGER :: iext 
     420      INTEGER :: indx_std 
     421      INTEGER :: iadd_std 
    420422 
    421423      IF ( PRESENT( padd ) ) THEN 
     
    431433      ENDIF 
    432434 
     435      iadd_std = 0 
     436      indx_std = -1 
     437      IF ( surfdata%nextra > 0 ) THEN 
     438         DO je = 1, surfdata%nextra 
     439           IF ( TRIM( surfdata%cext(je) ) == 'STD' ) THEN 
     440             iadd_std = 1 
     441             indx_std = je 
     442           ENDIF 
     443         END DO 
     444      ENDIF 
     445       
    433446      CALL init_obfbdata( fbdata ) 
    434447 
     
    440453 
    441454         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
    442             &                 2 + iadd, 1 + iext, .TRUE. ) 
     455            &                 2 + iadd + iadd_std, 1 + iext, .TRUE. ) 
    443456 
    444457         clfiletype = 'slafb' 
     
    461474         fbdata%cgrid(1)      = 'T' 
    462475         DO ja = 1, iadd 
    463             fbdata%caddname(2+ja) = padd%cdname(ja) 
    464             fbdata%caddlong(2+ja,1) = padd%cdlong(ja,1) 
    465             fbdata%caddunit(2+ja,1) = padd%cdunit(ja,1) 
     476            fbdata%caddname(2+iadd_std+ja) = padd%cdname(ja) 
     477            fbdata%caddlong(2+iadd_std+ja,1) = padd%cdlong(ja,1) 
     478            fbdata%caddunit(2+iadd_std+ja,1) = padd%cdunit(ja,1) 
    466479         END DO 
    467480 
     
    597610       
    598611         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
    599             &                 1 + iadd, iext, .TRUE. ) 
     612            &                 1 + iadd + iadd_std, iext, .TRUE. ) 
    600613 
    601614         fbdata%cname(1)      = surfdata%cvars(1) 
     
    615628         fbdata%cgrid(1)      = clgrid 
    616629         DO ja = 1, iadd 
    617             fbdata%caddname(1+ja) = padd%cdname(ja) 
    618             fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
    619             fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     630            fbdata%caddname(1+iadd_std+ja) = padd%cdname(ja) 
     631            fbdata%caddlong(1+iadd_std+ja,1) = padd%cdlong(ja,1) 
     632            fbdata%caddunit(1+iadd_std+ja,1) = padd%cdunit(ja,1) 
    620633         END DO 
    621634 
     
    623636       
    624637      fbdata%caddname(1)   = 'Hx' 
    625  
     638      IF ( indx_std /= -1 ) THEN 
     639         IF ( TRIM(surfdata%cvars(1)) == 'SLA' ) iadd_std = iadd_std + 1 
     640         fbdata%caddname(1+iadd_std)   = surfdata%cext(indx_std) 
     641         fbdata%caddlong(1+iadd_std,1) = 'Obs error standard deviation' 
     642         fbdata%caddunit(1+iadd_std,1) = fbdata%cobunit(1) 
     643      ENDIF 
     644       
    626645      WRITE(clfname, FMT="(A,'_fdbk_',I4.4,'.nc')") TRIM(clfiletype), nproc 
    627646 
     
    688707         fbdata%iobsk(1,jo,1)  = 0 
    689708         IF ( TRIM(surfdata%cvars(1)) == 'SLA' ) fbdata%pext(1,jo,1) = surfdata%rext(jo,2) 
     709         IF ( indx_std /= -1 ) THEN 
     710            fbdata%padd(1,jo,1+iadd_std,1) = surfdata%rext(jo,indx_std) 
     711         ENDIF 
     712          
    690713         DO ja = 1, iadd 
    691             fbdata%padd(1,jo,2+ja,1) = & 
     714            fbdata%padd(1,jo,2+iadd_std+ja,1) = & 
    692715               & surfdata%rext(jo,padd%ipoint(ja)) 
    693716         END DO 
Note: See TracChangeset for help on using the changeset viewer.