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 7489 – NEMO

Changeset 7489


Ignore:
Timestamp:
2016-12-12T12:27:44+01:00 (7 years ago)
Author:
dford
Message:

Changes to reject BGC obs at open boundaries, and update getting chlorophyll from FABM.

Location:
branches/UKMO/dev_r4650_general_vert_coord_obsoper_surf_bgc/NEMOGCM/NEMO/OPA_SRC/OBS
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r4650_general_vert_coord_obsoper_surf_bgc/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r7480 r7489  
    14501450#elif defined key_fabm 
    14511451      USE fabm 
    1452       USE trcsms_fabm, ONLY: model      ! ERSEM chlorophyll, fCO2 and pCO2 
     1452      USE par_fabm 
    14531453#endif 
    14541454#if defined key_spm 
     
    14921492      INTEGER :: jn                     ! loop index 
    14931493#if defined key_fabm 
    1494       INTEGER :: chl_index 
    14951494      REAL(wp), DIMENSION(jpi,jpj,jpk) :: logchl_3d 
    14961495#endif 
     
    16111610         logchl(:,:) = MEDUSA_CHL(:,:,1)    ! (not log) chlorophyll from HadOCC 
    16121611#elif defined key_fabm 
    1613          DO jn = 1, SIZE(model%diagnostic_variables) 
    1614             IF (TRIM(model%diagnostic_variables(jn)%standard_variable%name) == 'total_chlorophyll') THEN 
    1615                chl_index = jn 
    1616                EXIT 
    1617             ENDIF 
    1618          END DO 
    1619          logchl_3d(:,:,:) = fabm_get_bulk_diagnostic_data(model, chl_index) 
     1612         logchl_3d(:,:,:) = fabm_get_bulk_diagnostic_data(model, jp_fabmdia_chltot) 
    16201613         logchl(:,:) = logchl_3d(:,:,1) 
    16211614#else 
  • branches/UKMO/dev_r4650_general_vert_coord_obsoper_surf_bgc/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r7480 r7489  
    14231423      INTEGER :: inlasobs     !  - close to land 
    14241424      INTEGER :: igrdobs      !  - fail the grid search 
     1425      INTEGER :: ibdysobs     !  - close to open boundary 
    14251426                              ! Global counters for observations that 
    14261427      INTEGER :: iotdobsmpp   !  - outside time domain 
     
    14291430      INTEGER :: inlasobsmpp  !  - close to land 
    14301431      INTEGER :: igrdobsmpp   !  - fail the grid search 
     1432      INTEGER :: ibdysobsmpp  !  - close to open boundary 
    14311433      LOGICAL, DIMENSION(:), ALLOCATABLE :: &  
    14321434         & llvalid            ! data selection 
     
    14341436      INTEGER :: jstp         ! Time loop variable 
    14351437      INTEGER :: inrc         ! Time index variable 
     1438      INTEGER :: irec         ! Record index 
    14361439 
    14371440      IF (lwp) WRITE(numout,*)'obs_pre_logchl : Preparing the logchl observations...' 
     
    14531456      ilansobs = 0 
    14541457      inlasobs = 0 
     1458      ibdysobs = 0 
    14551459 
    14561460      ! ----------------------------------------------------------------------- 
     
    14831487         &                 tmask(:,:,1),    logchldata%nqc,  & 
    14841488         &                 iosdsobs,        ilansobs,        & 
    1485          &                 inlasobs,        ld_nea           )  
     1489         &                 inlasobs,        ld_nea,          & 
     1490         &                 ibdysobs,        ln_bound_reject  )  
    14861491          
    14871492      CALL obs_mpp_sum_integer( iosdsobs, iosdsobsmpp ) 
    14881493      CALL obs_mpp_sum_integer( ilansobs, ilansobsmpp ) 
    14891494      CALL obs_mpp_sum_integer( inlasobs, inlasobsmpp ) 
     1495      CALL obs_mpp_sum_integer( ibdysobs, ibdysobsmpp ) 
    14901496 
    14911497      ! ----------------------------------------------------------------------- 
     
    15361542               &            inlasobsmpp 
    15371543         ENDIF 
     1544         WRITE(numout,*) ' Remaining logchl data near open boundary (removed) = ', & 
     1545           &            ibdysobsmpp 
    15381546         WRITE(numout,*) ' logchl data accepted                             = ', & 
    15391547            &            logchldatqc%nsurfmpp 
     
    16061614      INTEGER :: inlasobs     !  - close to land 
    16071615      INTEGER :: igrdobs      !  - fail the grid search 
     1616      INTEGER :: ibdysobs     !  - close to open boundary 
    16081617                              ! Global counters for observations that 
    16091618      INTEGER :: iotdobsmpp   !  - outside time domain 
     
    16121621      INTEGER :: inlasobsmpp  !  - close to land 
    16131622      INTEGER :: igrdobsmpp   !  - fail the grid search 
     1623      INTEGER :: ibdysobsmpp  !  - close to open boundary 
    16141624      LOGICAL, DIMENSION(:), ALLOCATABLE :: &  
    16151625         & llvalid            ! data selection 
     
    16171627      INTEGER :: jstp         ! Time loop variable 
    16181628      INTEGER :: inrc         ! Time index variable 
     1629      INTEGER :: irec         ! Record index 
    16191630 
    16201631      IF (lwp) WRITE(numout,*)'obs_pre_spm : Preparing the spm observations...' 
     
    16361647      ilansobs = 0 
    16371648      inlasobs = 0 
     1649      ibdysobs = 0 
    16381650 
    16391651      ! ----------------------------------------------------------------------- 
     
    16661678         &                 tmask(:,:,1),    spmdata%nqc,  & 
    16671679         &                 iosdsobs,        ilansobs,        & 
    1668          &                 inlasobs,        ld_nea           )  
     1680         &                 inlasobs,        ld_nea,          & 
     1681         &                 ibdysobs,        ln_bound_reject  )  
    16691682          
    16701683      CALL obs_mpp_sum_integer( iosdsobs, iosdsobsmpp ) 
    16711684      CALL obs_mpp_sum_integer( ilansobs, ilansobsmpp ) 
    16721685      CALL obs_mpp_sum_integer( inlasobs, inlasobsmpp ) 
     1686      CALL obs_mpp_sum_integer( ibdysobs, ibdysobsmpp ) 
    16731687 
    16741688      ! ----------------------------------------------------------------------- 
     
    17191733               &            inlasobsmpp 
    17201734         ENDIF 
     1735         WRITE(numout,*) ' Remaining spm data near open boundary (removed) = ', & 
     1736            &            ibdysobsmpp 
    17211737         WRITE(numout,*) ' spm data accepted                             = ', & 
    17221738            &            spmdatqc%nsurfmpp 
     
    17891805      INTEGER :: inlasobs     !  - close to land 
    17901806      INTEGER :: igrdobs      !  - fail the grid search 
     1807      INTEGER :: ibdysobs     !  - close to open boundary 
    17911808                              ! Global counters for observations that 
    17921809      INTEGER :: iotdobsmpp   !  - outside time domain 
     
    17951812      INTEGER :: inlasobsmpp  !  - close to land 
    17961813      INTEGER :: igrdobsmpp   !  - fail the grid search 
     1814      INTEGER :: ibdysobsmpp  !  - close to open boundary 
    17971815      LOGICAL, DIMENSION(:), ALLOCATABLE :: &  
    17981816         & llvalid            ! data selection 
     
    18001818      INTEGER :: jstp         ! Time loop variable 
    18011819      INTEGER :: inrc         ! Time index variable 
     1820      INTEGER :: irec         ! Record index 
    18021821 
    18031822      IF (lwp) WRITE(numout,*)'obs_pre_fco2 : Preparing the fco2 observations...' 
     
    18191838      ilansobs = 0 
    18201839      inlasobs = 0 
     1840      ibdysobs = 0 
    18211841 
    18221842      ! ----------------------------------------------------------------------- 
     
    18491869         &                 tmask(:,:,1),    fco2data%nqc,  & 
    18501870         &                 iosdsobs,        ilansobs,        & 
    1851          &                 inlasobs,        ld_nea           )  
     1871         &                 inlasobs,        ld_nea,          & 
     1872         &                 ibdysobs,        ln_bound_reject  )  
    18521873          
    18531874      CALL obs_mpp_sum_integer( iosdsobs, iosdsobsmpp ) 
    18541875      CALL obs_mpp_sum_integer( ilansobs, ilansobsmpp ) 
    18551876      CALL obs_mpp_sum_integer( inlasobs, inlasobsmpp ) 
     1877      CALL obs_mpp_sum_integer( ibdysobs, ibdysobsmpp ) 
    18561878 
    18571879      ! ----------------------------------------------------------------------- 
     
    19021924               &            inlasobsmpp 
    19031925         ENDIF 
     1926         WRITE(numout,*) ' Remaining fco2 data near open boundary (removed) = ', & 
     1927           &            ibdysobsmpp 
    19041928         WRITE(numout,*) ' fco2 data accepted                             = ', & 
    19051929            &            fco2datqc%nsurfmpp 
     
    19721996      INTEGER :: inlasobs     !  - close to land 
    19731997      INTEGER :: igrdobs      !  - fail the grid search 
     1998      INTEGER :: ibdysobs     !  - close to open boundary 
    19741999                              ! Global counters for observations that 
    19752000      INTEGER :: iotdobsmpp   !  - outside time domain 
     
    19782003      INTEGER :: inlasobsmpp  !  - close to land 
    19792004      INTEGER :: igrdobsmpp   !  - fail the grid search 
     2005      INTEGER :: ibdysobsmpp  !  - close to open boundary 
    19802006      LOGICAL, DIMENSION(:), ALLOCATABLE :: &  
    19812007         & llvalid            ! data selection 
     
    19832009      INTEGER :: jstp         ! Time loop variable 
    19842010      INTEGER :: inrc         ! Time index variable 
     2011      INTEGER :: irec         ! Record index 
    19852012 
    19862013      IF (lwp) WRITE(numout,*)'obs_pre_pco2 : Preparing the pco2 observations...' 
     
    20022029      ilansobs = 0 
    20032030      inlasobs = 0 
     2031      ibdysobs = 0 
    20042032 
    20052033      ! ----------------------------------------------------------------------- 
     
    20322060         &                 tmask(:,:,1),    pco2data%nqc,  & 
    20332061         &                 iosdsobs,        ilansobs,        & 
    2034          &                 inlasobs,        ld_nea           )  
     2062         &                 inlasobs,        ld_nea,          & 
     2063         &                 ibdysobs,        ln_bound_reject  )  
    20352064          
    20362065      CALL obs_mpp_sum_integer( iosdsobs, iosdsobsmpp ) 
    20372066      CALL obs_mpp_sum_integer( ilansobs, ilansobsmpp ) 
    20382067      CALL obs_mpp_sum_integer( inlasobs, inlasobsmpp ) 
     2068      CALL obs_mpp_sum_integer( ibdysobs, ibdysobsmpp ) 
    20392069 
    20402070      ! ----------------------------------------------------------------------- 
     
    20852115               &            inlasobsmpp 
    20862116         ENDIF 
     2117         WRITE(numout,*) ' Remaining pco2 data near open boundary (removed) = ', & 
     2118           &            ibdysobsmpp 
    20872119         WRITE(numout,*) ' pco2 data accepted                             = ', & 
    20882120            &            pco2datqc%nsurfmpp 
Note: See TracChangeset for help on using the changeset viewer.