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 4048 for branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC – NEMO

Ignore:
Timestamp:
2013-10-02T18:32:18+02:00 (11 years ago)
Author:
djlea
Message:

Cleaning and debugging of the observation operator. Turn off the night time averaging of SST data by default, but add a namelist option to switch it on.

Location:
branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/off_data.F90

    r4030 r4048  
    33   IMPLICIT NONE 
    44   INTEGER, PARAMETER :: MaxNumFiles = 1000 
     5 
    56   !! Class 4 file settings 
    67   INTEGER :: & 
    7            &  cl4_fclen, &            !: number of forecast days 
    8            &  jimatch, &              !: current match 
    9            &  n_match                 !: number of matches 
     8           & cl4_fcst_idx(MaxNumFiles), & !: forecast indices 
     9           & cl4_match_len, &             !: number of match types 
     10           & cl4_fcst_len                 !: number of forecast days 
    1011   CHARACTER(len=lc) :: & 
    11            & cl4_vars(MaxNumFiles), & !: class 4 variables 
    12            & cl4_sys, &               !: class 4 system 
    13            & cl4_cfg, &               !: class 4 configuration 
    14            & cl4_date, &              !: class 4 date 
    15            & cl4_vn,  &               !: class 4 version 
    16            & cl4_prefix, &            !: class 4 prefix 
    17            & cl4_contact, &           !: class 4 contact 
    18            & cl4_inst                 !: class 4 institute 
    19    REAL ::   cl4_modjuld              !: model Julian day 
     12           & cl4_vars(MaxNumFiles), &  !: class 4 variables 
     13           & cl4_sys, &                !: class 4 system 
     14           & cl4_cfg, &                !: class 4 configuration 
     15           & cl4_date, &               !: class 4 date 
     16           & cl4_vn,  &                !: class 4 version 
     17           & cl4_prefix, &             !: class 4 prefix 
     18           & cl4_contact, &            !: class 4 contact 
     19           & cl4_inst                  !: class 4 institute 
     20   REAL ::   cl4_modjuld               !: model Julian day 
    2021   REAL :: & 
    21       & cl4_leadtime(MaxNumFiles)     !: Lead time data 
     22      & cl4_leadtime(MaxNumFiles)      !: Lead time data 
     23 
    2224   !! Offline obs_oper settings 
    2325   CHARACTER(len=lc) :: & 
    24       & model_files(MaxNumFiles)      !: model files 
     26      & off_files(MaxNumFiles)         !: model files 
    2527   INTEGER            :: & 
    26       & nn_modindex(MaxNumFiles), &   !: model file indices 
    27       & nn_forecast(MaxNumFiles)      !: forecast indices 
     28      & jifile, &                      !: current file list index 
     29      & n_files, &                     !: number of files 
     30      & jimatch, &                     !: current match 
     31      & nn_off_idx(MaxNumFiles), &     !: time_counter indices 
     32      & nn_off_freq                    !: read frequency in time steps 
    2833   CHARACTER(len=128) :: & 
    29       & alt_file                      !: altimeter file 
     34      & alt_file                       !: altimeter file 
    3035CONTAINS 
    3136   SUBROUTINE off_data_init( ld_cl4 ) 
     
    4449 
    4550      ! Standard offline obs_oper information 
    46       NAMELIST/namoff/model_files, nn_modindex, nn_forecast 
     51      NAMELIST/namoff/off_files, nn_off_idx, nn_off_freq 
    4752 
    4853      ! Class 4 file specifiers 
    4954      NAMELIST/namcl4/cl4_vars, cl4_sys, cl4_cfg, cl4_date, cl4_vn, & 
    5055         &            cl4_prefix, cl4_contact, cl4_inst, cl4_leadtime, & 
    51          &            cl4_fclen 
     56         &            cl4_fcst_idx, cl4_fcst_len, cl4_match_len 
    5257 
    5358      ! Standard offline obs_oper initialisation 
    54       jimatch = 0                   !: match iteration variable  
    55       n_match = 0                   !: number of matches to perform 
    56       model_files(:) = ''           !: list of files to read in 
    57       nn_modindex(:) = 0            !: list of indices inside each file 
     59      jimatch = 0                   !: match-up iteration variable  
     60      jifile = 1                    !: input file iteration variable  
     61      n_files = 0                   !: number of files to cycle through 
     62      off_files(:) = ''             !: list of files to read in 
     63      nn_off_idx(:) = 0             !: list of indices inside each file 
     64      nn_off_freq = -1              !: input frequency in time steps 
    5865 
    5966      ! Class 4 initialisation 
    6067      cl4_leadtime(:) = 0           !: Lead time axis value for each file 
    61       cl4_fclen = 0                 !: Length of the forecast dimension 
     68      cl4_fcst_len = 0              !: Length of the forecast dimension 
     69      cl4_match_len = 1             !: Number of match types 
     70      cl4_fcst_idx(:) = 0           !: output file forecast index 
    6271      cl4_vars(:) = ''              !: output file variable names 
    6372      cl4_sys = ''                  !: output file system 
     
    7786      ENDIF 
    7887 
    79       ! count forecast/persistence files 
     88      ! count input files 
    8089      lmask(:) = .FALSE. 
    81       WHERE (model_files(:) /= '') lmask(:) = .TRUE. 
    82       n_match = COUNT(lmask) 
     90      WHERE (off_files(:) /= '') lmask(:) = .TRUE. 
     91      n_files = COUNT(lmask) 
    8392 
     93      !! Initialise sub obs window frequency 
     94      IF (nn_off_freq == -1) THEN 
     95         !! Run length 
     96         nn_off_freq = nitend - nit000 + 1 
     97      ENDIF 
     98 
     99      !! Print summary of settings 
    84100      IF(lwp) THEN 
    85101         WRITE(numout,*) 
     
    87103         WRITE(numout,*) '~~~~~~~~~~~~~~~~~' 
    88104         WRITE(numout,*) '   Namelist namoff : set offline obs_oper parameters'  
    89          DO jf = 1, n_match 
     105         DO jf = 1, n_files 
    90106            WRITE(numout,'(1X,2A)') '   Input forecast file name          forecastfile = ', & 
    91                TRIM(model_files(jf)) 
     107               TRIM(off_files(jf)) 
    92108            WRITE(numout,*) '   Input forecast file index        forecastindex = ', & 
    93                nn_modindex(jf) 
    94             WRITE(numout,*) '   Input forecast leadtime index    leadtimeindex = ', & 
    95                nn_forecast(jf) 
    96             WRITE(numout,*) '   Input forecast leadtime value    leadtimevalue = ', & 
     109               nn_off_idx(jf) 
     110            WRITE(numout,*) '   Output forecast leadtime index   leadtimeindex = ', & 
     111               cl4_fcst_idx(jf) 
     112            WRITE(numout,*) '   Output forecast leadtime value   leadtimevalue = ', & 
    97113               cl4_leadtime(jf) 
    98114            WRITE(numout,'(1X,2A)') '   Input class 4 variable       class 4 parameter = ', & 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/off_oper.F90

    r4031 r4048  
    4040         CALL off_oper_init 
    4141         !! Loop over various model counterparts 
    42          DO jimatch = 1, n_match 
     42         DO jimatch = 1, cl4_match_len 
    4343            IF (jimatch .GT. 1) THEN 
    4444               !! Initialise obs_oper 
    4545               CALL dia_obs_init 
    4646            END IF 
    47             !! Read next model counterpart 
    48             CALL off_rea_dri 
    4947            !! Interpolate to observation space 
    5048            CALL off_oper_interp 
     
    6462         !! ** Purpose : To interpolate the model as if it were running online. 
    6563         !! 
     64         !! ** Method : 1. Populate model counterparts 
     65         !!             2. Call dia_obs at appropriate time steps 
    6666         !!---------------------------------------------------------------------- 
    6767         IMPLICIT NONE 
    6868         INTEGER :: istp ! time step index 
     69         !! Loop over entire run 
    6970         istp = nit000 
    7071         nstop = 0 
    7172         DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    72             CALL dia_obs(istp) 
     73            IF (jifile <= n_files + 1) THEN 
     74               IF ( MOD(istp, nn_off_freq) == nit000 ) THEN 
     75                  !! Read next model counterpart 
     76                  CALL off_rea_dri(jifile) 
     77                  jifile = jifile + 1 
     78               ENDIF 
     79               !! Interpolate single time step 
     80               CALL dia_obs(istp) 
     81            ENDIF 
     82            !! Increment model step 
    7383            istp = istp + 1 
    7484         END DO 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/off_read.F90

    r4031 r4048  
    2323 
    2424CONTAINS 
    25    SUBROUTINE off_rea_dri 
     25   SUBROUTINE off_rea_dri(kfile) 
    2626      IMPLICIT NONE 
     27      INTEGER, INTENT(IN) :: & 
     28              & kfile         !: File number 
    2729      CHARACTER(len=lc) :: & 
    2830              & cdfilename, & !: File name 
     
    3032      INTEGER :: & 
    3133              & kindex       !: File index to read 
    32       cdfilename = TRIM(model_files(jimatch)) 
    33       cmatchname = TRIM(cl4_vars(jimatch)) 
    34       kindex = nn_modindex(jimatch) 
    35       IF (TRIM(cmatchname) == 'forecast') THEN 
    36          CALL off_read_dailymean(TRIM(cdfilename), kindex) 
    37          CALL off_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
    38       ELSE IF (TRIM(cmatchname) == 'persistence') THEN 
    39          CALL off_read_dailymean(TRIM(cdfilename), kindex) 
     34  
     35      !! Filename, index and match-up kind 
     36      cdfilename = TRIM(off_files(kfile)) 
     37      cmatchname = TRIM(cl4_vars(kfile)) 
     38      kindex = nn_off_idx(kfile) 
     39 
     40      !! Update model fields 
     41      !! Class 4 variables: forecast, persistence, 
     42      !!                    nrt_analysis, best_estimate 
     43      !! Feedback variables: empty string 
     44      IF ( (TRIM(cmatchname) == 'forecast') .OR. & 
     45         & (TRIM(cmatchname) == 'persistence') .OR. & 
     46         & (TRIM(cmatchname) == 'nrt_analysis') .OR. & 
     47         & (TRIM(cmatchname) == 'best_estimate').OR. & 
     48         & (TRIM(cmatchname) == '') ) THEN 
     49         CALL off_read_file(TRIM(cdfilename), kindex) 
    4050         CALL off_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
    4151      ELSE IF (TRIM(cmatchname) == 'climatology') THEN 
     
    4454         CALL off_read_altbias(TRIM(cdfilename)) 
    4555         CALL off_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
    46       ELSE IF (TRIM(cmatchname) == '') THEN 
    47          ! Feedback file settings 
    48          CALL off_read_dailymean(TRIM(cdfilename), kindex) 
    49          CALL off_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
    5056      END IF 
     57 
    5158   END SUBROUTINE off_rea_dri 
    5259 
     
    8390      ELSE 
    8491         ! Open Netcdf file to find dimension id 
    85          istat = nf90_open(trim(filename),nf90_noclobber,ncid) 
     92         istat = nf90_open(trim(filename),nf90_nowrite,ncid) 
    8693         istat = nf90_inq_dimid(ncid,'x',xdim) 
    8794         istat = nf90_inq_dimid(ncid,'y',ydim) 
     
    127134   END SUBROUTINE off_read_altbias 
    128135 
    129    SUBROUTINE off_read_dailymean(filename, ifcst) 
     136   SUBROUTINE off_read_file(filename, ifcst) 
    130137      IMPLICIT NONE 
    131138      !------------------------------------------------------------------------ 
    132139      ! 
    133       !             ** off_read_dailymean ** 
     140      !             ** off_read_file ** 
    134141      ! 
    135142      ! Purpose : To fill tn and sn with dailymean field from netcdf files 
     
    255262         istat = nf90_close(ncid) 
    256263      END IF 
    257    END SUBROUTINE off_read_dailymean 
     264   END SUBROUTINE off_read_file 
    258265 
    259266   SUBROUTINE off_read_juld(filename, ifcst, julian) 
     
    291298      time_str='' 
    292299      !! Read in time_counter and remainder seconds 
    293       istat = nf90_open(trim(filename),nf90_noclobber,ncid) 
     300      istat = nf90_open(trim(filename),nf90_nowrite,ncid) 
    294301      istat = nf90_inq_dimid(ncid,'time_counter',dimid) 
    295302      IF (istat /= nf90_noerr) THEN 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/off_write.F90

    r4031 r4048  
    2323 
    2424   INTERFACE off_wri_extra 
    25       MODULE PROCEDURE off_wri_extra_3d, off_wri_extra_4d, off_wri_extra_4d_index 
     25      MODULE PROCEDURE off_wri_extra_3d_index, off_wri_extra_4d, off_wri_extra_4d_index 
    2626   END INTERFACE 
    2727 
    2828   CONTAINS 
    2929 
    30       SUBROUTINE off_wri_extra_3d(cdfilename, cdvarname, ndeps, nvars, & 
    31                                &  nobs, pdata) 
     30      SUBROUTINE off_wri_extra_3d_index(cdfilename, cdvarname, ndeps, nvars, & 
     31                               &  nobs, kstart, kcount, pdata) 
    3232         !!---------------------------------------------------------------------- 
    3333         !!                    ***  ROUTINE off_wri_extra_3d  *** 
     
    4343                 & cdfilename, & !: netcdf file name 
    4444                 & cdvarname     !: netcdf variable name 
     45         INTEGER, DIMENSION(3), INTENT(IN) :: & 
     46                 & kstart, &     !: start indices 
     47                 & kcount        !: count indices 
    4548         REAL(KIND=cldp), DIMENSION(ndeps, nvars, nobs), INTENT(IN) :: & 
    4649                 & pdata         !: 3d data 
     
    5457         ! Write data 
    5558         CALL chkerr(nf90_inq_varid(ncid,TRIM(cdvarname), varid),cpname, __LINE__ ) 
    56          CALL chkerr(nf90_put_var(ncid, varid, pdata),cpname, __LINE__ ) 
     59         CALL chkerr(nf90_put_var(ncid, varid, pdata, kstart, kcount),cpname, __LINE__ ) 
    5760         ! Close netcdf file 
    5861         CALL chkerr(nf90_close(ncid), cpname, __LINE__ ) 
    59       END SUBROUTINE off_wri_extra_3d 
     62      END SUBROUTINE off_wri_extra_3d_index 
    6063 
    6164      SUBROUTINE off_wri_extra_4d_index(cdfilename, cdvarname, ndeps, nfcst, & 
     
    249252      END SUBROUTINE off_wri_default 
    250253 
    251       SUBROUTINE off_wri_init(cconf, csys, ckind, cversion, cdate, & 
    252                             & nproc, nobs, nvars, ndeps, nfcst, & 
    253                             & cdfilename) 
     254      SUBROUTINE off_wri_init(cconf, csys, ckind, cversion, ccont, & 
     255                            & cinst, cdate, nproc, nobs, nvars, & 
     256                            & ndeps, nfcst, cdfilename) 
    254257         !!---------------------------------------------------------------------- 
    255258         !!                    ***  ROUTINE off_wri_init  *** 
     
    265268                 & ckind, &      !: observation kind e.g. profile 
    266269                 & cversion, &   !: model version e.g. 12.0 
     270                 & ccont, &      !: contact email 
     271                 & cinst, &      !: institution description 
    267272                 & cdate         !: e.g. yyyymmdd 
    268273         INTEGER, INTENT(IN) :: & 
     
    358363               & TRIM(ref_date) ), cpname, __LINE__ ) 
    359364            CALL chkerr( nf90_put_att(ncid, nf90_global, 'contact', & 
    360                & 'andrew.ryan@metoffice.gov.uk' ), cpname, __LINE__ ) 
     365               & TRIM(ccont) ), cpname, __LINE__ ) 
    361366            CALL chkerr( nf90_put_att(ncid, nf90_global, 'obs_type', & 
    362367               & TRIM(ckind) ), cpname, __LINE__ ) 
     
    365370            CALL chkerr( nf90_put_att(ncid, nf90_global, 'configuration', & 
    366371               & TRIM(cconf) ), cpname, __LINE__ )  
    367            CALL chkerr( nf90_put_att(ncid, nf90_global, 'institution', & 
    368               & 'UK Met Office' ), cpname, __LINE__ )  
     372            CALL chkerr( nf90_put_att(ncid, nf90_global, 'institution', & 
     373               & TRIM(cinst) ), cpname, __LINE__ )  
    369374 
    370375            !! Define Dimensions 
Note: See TracChangeset for help on using the changeset viewer.