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 8687 for branches/UKMO – NEMO

Changeset 8687 for branches/UKMO


Ignore:
Timestamp:
2017-11-09T18:28:30+01:00 (6 years ago)
Author:
dford
Message:

Initial (as yet untested) implementation of additional surface BGC types.

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

Legend:

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

    r8653 r8687  
    9595      & profdataqc           !: Profile data after quality control 
    9696 
    97    CHARACTER(len=6), PUBLIC, DIMENSION(:), ALLOCATABLE :: & 
     97   CHARACTER(len=25), PUBLIC, DIMENSION(:), ALLOCATABLE :: & 
    9898      & cobstypesprof, &     !: Profile obs types 
    9999      & cobstypessurf        !: Surface obs types 
     
    143143 
    144144      CHARACTER(len=128), DIMENSION(jpmaxnfiles) :: & 
    145          & cn_profbfiles,    &   ! T/S profile input filenames 
    146          & cn_sstfbfiles,    &   ! Sea surface temperature input filenames 
    147          & cn_slafbfiles,    &   ! Sea level anomaly input filenames 
    148          & cn_sicfbfiles,    &   ! Seaice concentration input filenames 
    149          & cn_velfbfiles,    &   ! Velocity profile input filenames 
    150          & cn_sssfbfiles,    &   ! Sea surface salinity input filenames 
    151          & cn_logchlfbfiles, &   ! Log(Chl) input filenames 
    152          & cn_spmfbfiles,    &   ! Sediment input filenames 
    153          & cn_fco2fbfiles,   &   ! fco2 input filenames 
    154          & cn_pco2fbfiles,   &   ! pco2 input filenames 
    155          & cn_sstbiasfiles       ! SST bias input filenames 
     145         & cn_profbfiles,                 & ! T/S profile input filenames 
     146         & cn_sstfbfiles,                 & ! Sea surface temperature input filenames 
     147         & cn_slafbfiles,                 & ! Sea level anomaly input filenames 
     148         & cn_sicfbfiles,                 & ! Seaice concentration input filenames 
     149         & cn_velfbfiles,                 & ! Velocity profile input filenames 
     150         & cn_sssfbfiles,                 & ! Sea surface salinity input filenames 
     151         & cn_surf_logchl_totalfbfiles,   & ! Surface total              log10(chlorophyll) input filenames 
     152         & cn_surf_logchl_diatfbfiles,    & ! Surface diatom             log10(chlorophyll) input filenames 
     153         & cn_surf_logchl_nondiatfbfiles, & ! Surface non-diatom         log10(chlorophyll) input filenames 
     154         & cn_surf_logchl_dinofbfiles,    & ! Surface dinoflagellate     log10(chlorophyll) input filenames 
     155         & cn_surf_logchl_microfbfiles,   & ! Surface microphytoplankton log10(chlorophyll) input filenames 
     156         & cn_surf_logchl_nanofbfiles,    & ! Surface nanophytoplankton  log10(chlorophyll) input filenames 
     157         & cn_surf_logchl_picofbfiles,    & ! Surface picophytoplankton  log10(chlorophyll) input filenames 
     158         & cn_surf_chl_totalfbfiles,      & ! Surface total              chlorophyll        input filenames 
     159         & cn_surf_spmfbfiles,            & ! Surface suspended particulate matter input filenames 
     160         & cn_surf_fco2fbfiles,           & ! Surface fugacity         of carbon dioxide input filenames 
     161         & cn_surf_pco2fbfiles,           & ! Surface partial pressure of carbon dioxide input filenames 
     162         & cn_sstbiasfiles                  ! SST bias input filenames 
    156163 
    157164      CHARACTER(LEN=128) :: & 
     
    159166 
    160167 
    161       LOGICAL :: ln_t3d          ! Logical switch for temperature profiles 
    162       LOGICAL :: ln_s3d          ! Logical switch for salinity profiles 
    163       LOGICAL :: ln_sla          ! Logical switch for sea level anomalies  
    164       LOGICAL :: ln_sst          ! Logical switch for sea surface temperature 
    165       LOGICAL :: ln_sic          ! Logical switch for sea ice concentration 
    166       LOGICAL :: ln_sss          ! Logical switch for sea surface salinity obs 
    167       LOGICAL :: ln_vel3d        ! Logical switch for velocity (u,v) obs 
    168       LOGICAL :: ln_logchl       ! Logical switch for log(Chl) obs 
    169       LOGICAL :: ln_spm          ! Logical switch for sediment obs 
    170       LOGICAL :: ln_fco2         ! Logical switch for fco2 obs 
    171       LOGICAL :: ln_pco2         ! Logical switch for pco2 obs 
    172       LOGICAL :: ln_nea          ! Logical switch to remove obs near land 
    173       LOGICAL :: ln_altbias      ! Logical switch for altimeter bias 
    174       LOGICAL :: ln_sstbias      ! Logical switch for bias correction of SST 
    175       LOGICAL :: ln_ignmis       ! Logical switch for ignoring missing files 
    176       LOGICAL :: ln_s_at_t       ! Logical switch to compute model S at T obs 
    177       LOGICAL :: ln_bound_reject ! Logical switch for rejecting obs near the boundary 
     168      LOGICAL :: ln_t3d                 ! Logical switch for temperature profiles 
     169      LOGICAL :: ln_s3d                 ! Logical switch for salinity profiles 
     170      LOGICAL :: ln_sla                 ! Logical switch for sea level anomalies  
     171      LOGICAL :: ln_sst                 ! Logical switch for sea surface temperature 
     172      LOGICAL :: ln_sic                 ! Logical switch for sea ice concentration 
     173      LOGICAL :: ln_sss                 ! Logical switch for sea surface salinity obs 
     174      LOGICAL :: ln_vel3d               ! Logical switch for velocity (u,v) obs 
     175      LOGICAL :: ln_surf_logchl_total   ! Logical switch for surface total              log10(chlorophyll) obs 
     176      LOGICAL :: ln_surf_logchl_diat    ! Logical switch for surface diatom             log10(chlorophyll) obs 
     177      LOGICAL :: ln_surf_logchl_nondiat ! Logical switch for surface non-diatom         log10(chlorophyll) obs 
     178      LOGICAL :: ln_surf_logchl_dino    ! Logical switch for surface dinoflagellate     log10(chlorophyll) obs 
     179      LOGICAL :: ln_surf_logchl_micro   ! Logical switch for surface microphytoplankton log10(chlorophyll) obs 
     180      LOGICAL :: ln_surf_logchl_nano    ! Logical switch for surface nanophytoplankton  log10(chlorophyll) obs 
     181      LOGICAL :: ln_surf_logchl_pico    ! Logical switch for surface picophytoplankton  log10(chlorophyll) obs 
     182      LOGICAL :: ln_surf_chl_total      ! Logical switch for surface total              chlorophyll        obs 
     183      LOGICAL :: ln_surf_spm            ! Logical switch for surface suspended particulate matter obs 
     184      LOGICAL :: ln_surf_fco2           ! Logical switch for surface fugacity         of carbon dioxide obs 
     185      LOGICAL :: ln_surf_pco2           ! Logical switch for surface partial pressure of carbon dioxide obs 
     186      LOGICAL :: ln_nea                 ! Logical switch to remove obs near land 
     187      LOGICAL :: ln_altbias             ! Logical switch for altimeter bias 
     188      LOGICAL :: ln_sstbias             ! Logical switch for bias correction of SST 
     189      LOGICAL :: ln_ignmis              ! Logical switch for ignoring missing files 
     190      LOGICAL :: ln_s_at_t              ! Logical switch to compute model S at T obs 
     191      LOGICAL :: ln_bound_reject        ! Logical switch for rejecting obs near the boundary 
    178192 
    179193      REAL(dp) :: rn_dobsini     ! Obs window start date YYYYMMDD.HHMMSS 
     
    200214      NAMELIST/namobs/ln_diaobs, ln_t3d, ln_s3d, ln_sla,              & 
    201215         &            ln_sst, ln_sic, ln_sss, ln_vel3d,               & 
    202          &            ln_logchl, ln_spm, ln_fco2, ln_pco2,            & 
     216         &            ln_surf_logchl_total,   ln_surf_logchl_diat,    & 
     217         &            ln_surf_logchl_nondiat, ln_surf_logchl_dino,    & 
     218         &            ln_surf_logchl_micro,   ln_surf_logchl_nano,    & 
     219         &            ln_surf_logchl_pico,    ln_surf_chl_total,      & 
     220         &            ln_surf_spm, ln_surf_fco2, ln_surf_pco2,        & 
    203221         &            ln_altbias, ln_sstbias, ln_nea,                 & 
    204222         &            ln_grid_global, ln_grid_search_lookup,          & 
     
    210228         &            cn_sstfbfiles, cn_sicfbfiles,                   & 
    211229         &            cn_velfbfiles, cn_sssfbfiles,                   & 
    212          &            cn_logchlfbfiles, cn_spmfbfiles,                & 
    213          &            cn_fco2fbfiles, cn_pco2fbfiles,                 & 
     230         &            cn_surf_logchl_totalfbfiles,                    & 
     231         &            cn_surf_logchl_diatfbfiles,                     & 
     232         &            cn_surf_logchl_nondiatfbfiles,                  & 
     233         &            cn_surf_logchl_dinofbfiles,                     & 
     234         &            cn_surf_logchl_microfbfiles,                    & 
     235         &            cn_surf_logchl_nanofbfiles,                     & 
     236         &            cn_surf_logchl_picofbfiles,                     & 
     237         &            cn_surf_chl_totalfbfiles, cn_surf_spmfbfiles,   & 
     238         &            cn_surf_fco2fbfiles, cn_surf_pco2fbfiles,       & 
    214239         &            cn_sstbiasfiles, cn_altbiasfile,                & 
    215240         &            cn_gridsearchfile, rn_gridsearchres,            & 
     
    237262 
    238263      ! Some namelist arrays need initialising 
    239       cn_profbfiles(:)    = '' 
    240       cn_slafbfiles(:)    = '' 
    241       cn_sstfbfiles(:)    = '' 
    242       cn_sicfbfiles(:)    = '' 
    243       cn_velfbfiles(:)    = '' 
    244       cn_sssfbfiles(:)    = '' 
    245       cn_logchlfbfiles(:) = '' 
    246       cn_spmfbfiles(:)    = '' 
    247       cn_fco2fbfiles(:)   = '' 
    248       cn_pco2fbfiles(:)   = '' 
    249       cn_sstbiasfiles(:)  = '' 
    250       nn_profdavtypes(:)  = -1 
     264      cn_profbfiles(:)                 = '' 
     265      cn_slafbfiles(:)                 = '' 
     266      cn_sstfbfiles(:)                 = '' 
     267      cn_sicfbfiles(:)                 = '' 
     268      cn_velfbfiles(:)                 = '' 
     269      cn_sssfbfiles(:)                 = '' 
     270      cn_surf_logchl_totalfbfiles(:)   = '' 
     271      cn_surf_logchl_diatfbfiles(:)    = '' 
     272      cn_surf_logchl_nondiatfbfiles(:) = '' 
     273      cn_surf_logchl_dinofbfiles(:)    = '' 
     274      cn_surf_logchl_microfbfiles(:)   = '' 
     275      cn_surf_logchl_nanofbfiles(:)    = '' 
     276      cn_surf_logchl_picofbfiles(:)    = '' 
     277      cn_surf_chl_totalfbfiles(:)      = '' 
     278      cn_surf_spmfbfiles(:)            = '' 
     279      cn_surf_fco2fbfiles(:)           = '' 
     280      cn_surf_pco2fbfiles(:)           = '' 
     281      cn_sstbiasfiles(:)               = '' 
     282      nn_profdavtypes(:)               = -1 
    251283 
    252284      CALL ini_date( rn_dobsini ) 
     
    286318         WRITE(numout,*) '             Logical switch for velocity observations               ln_vel3d = ', ln_vel3d 
    287319         WRITE(numout,*) '             Logical switch for SSS observations                      ln_sss = ', ln_sss 
    288          WRITE(numout,*) '             Logical switch for log(Chl) observations              ln_logchl = ', ln_logchl 
    289          WRITE(numout,*) '             Logical switch for SPM observations                      ln_spm = ', ln_spm 
    290          WRITE(numout,*) '             Logical switch for FCO2 observations                    ln_fco2 = ', ln_fco2 
    291          WRITE(numout,*) '             Logical switch for PCO2 observations                    ln_pco2 = ', ln_pco2 
     320         WRITE(numout,*) '             Logical switch for surf_logchl_total obs   ln_surf_logchl_total = ', ln_surf_logchl_total 
     321         WRITE(numout,*) '             Logical switch for surf_logchl_diat obs     ln_surf_logchl_diat = ', ln_surf_logchl_diat 
     322         WRITE(numout,*) '             Logical switch for surf_logchl_nondiat   ln_surf_logchl_nondiat = ', ln_surf_logchl_nondiat 
     323         WRITE(numout,*) '             Logical switch for surf_logchl_dino obs     ln_surf_logchl_dino = ', ln_surf_logchl_dino 
     324         WRITE(numout,*) '             Logical switch for surf_logchl_micro obs   ln_surf_logchl_micro = ', ln_surf_logchl_micro 
     325         WRITE(numout,*) '             Logical switch for surf_logchl_nano obs     ln_surf_logchl_nano = ', ln_surf_logchl_nano 
     326         WRITE(numout,*) '             Logical switch for surf_logchl_pico obs     ln_surf_logchl_pico = ', ln_surf_logchl_pico 
     327         WRITE(numout,*) '             Logical switch for surf_chl_total obs         ln_surf_chl_total = ', ln_surf_chl_total 
     328         WRITE(numout,*) '             Logical switch for surface SPM observations         ln_surf_spm = ', ln_surf_spm 
     329         WRITE(numout,*) '             Logical switch for surface fCO2 observations       ln_surf_fco2 = ', ln_surf_fco2 
     330         WRITE(numout,*) '             Logical switch for surface pCO2 observations       ln_surf_pco2 = ', ln_surf_pco2 
    292331         WRITE(numout,*) '             Global distribution of observations              ln_grid_global = ', ln_grid_global 
    293332         WRITE(numout,*) '             Logical switch for obs grid search lookup ln_grid_search_lookup = ', ln_grid_search_lookup 
     
    315354 
    316355      nproftypes = COUNT( (/ln_t3d .OR. ln_s3d, ln_vel3d /) ) 
    317       nsurftypes = COUNT( (/ln_sla, ln_sst, ln_sic, ln_sss, & 
    318          &                  ln_logchl, ln_spm, ln_fco2, ln_pco2 /) ) 
     356      nsurftypes = COUNT( (/ln_sla, ln_sst, ln_sic, ln_sss,              & 
     357         &                  ln_surf_logchl_total, ln_surf_logchl_diat,   & 
     358         &                  ln_surf_logchl_nondiat, ln_surf_logchl_dino, & 
     359         &                  ln_surf_logchl_micro, ln_surf_logchl_nano,   & 
     360         &                  ln_surf_logchl_pico, ln_surf_chl_total,      & 
     361         &                  ln_surf_spm, ln_surf_fco2, ln_surf_pco2 /) ) 
    319362 
    320363      IF ( nproftypes == 0 .AND. nsurftypes == 0 ) THEN 
     
    363406         IF (ln_sla) THEN 
    364407            jtype = jtype + 1 
    365             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sla   ', & 
     408            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sla', & 
    366409               &                   cn_slafbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    367             CALL obs_setinterpopts( nsurftypes, jtype, 'sla   ',      & 
     410            CALL obs_setinterpopts( nsurftypes, jtype, 'sla',         & 
    368411               &                  nn_2dint, nn_2dint_sla,             & 
    369412               &                  rn_sla_avglamscl, rn_sla_avgphiscl, & 
     
    374417         IF (ln_sst) THEN 
    375418            jtype = jtype + 1 
    376             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sst   ', & 
     419            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sst', & 
    377420               &                   cn_sstfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    378             CALL obs_setinterpopts( nsurftypes, jtype, 'sst   ',      & 
     421            CALL obs_setinterpopts( nsurftypes, jtype, 'sst',         & 
    379422               &                  nn_2dint, nn_2dint_sst,             & 
    380423               &                  rn_sst_avglamscl, rn_sst_avgphiscl, & 
     
    386429         IF (ln_sic) THEN 
    387430            jtype = jtype + 1 
    388             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sic   ', & 
     431            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sic', & 
    389432               &                   cn_sicfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    390             CALL obs_setinterpopts( nsurftypes, jtype, 'sic   ',      & 
     433            CALL obs_setinterpopts( nsurftypes, jtype, 'sic',         & 
    391434               &                  nn_2dint, nn_2dint_sic,             & 
    392435               &                  rn_sic_avglamscl, rn_sic_avgphiscl, & 
     
    398441         IF (ln_sss) THEN 
    399442            jtype = jtype + 1 
    400             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sss   ', & 
     443            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'sss', & 
    401444               &                   cn_sssfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    402             CALL obs_setinterpopts( nsurftypes, jtype, 'sss   ',      & 
     445            CALL obs_setinterpopts( nsurftypes, jtype, 'sss',         & 
    403446               &                  nn_2dint, nn_2dint_sss,             & 
    404447               &                  rn_sss_avglamscl, rn_sss_avgphiscl, & 
     
    408451         ENDIF 
    409452 
    410          IF (ln_logchl) THEN 
    411             jtype = jtype + 1 
    412             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'logchl', & 
     453         IF (ln_surf_logchl_total) THEN 
     454            jtype = jtype + 1 
     455            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_logchl_total', & 
    413456               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    414             CALL obs_setinterpopts( nsurftypes, jtype, 'logchl',         & 
     457            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_logchl_total',   & 
     458               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     459               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     460               &                    lfpindegs, llnightav ) 
     461         ENDIF 
     462 
     463         IF (ln_surf_logchl_diat) THEN 
     464            jtype = jtype + 1 
     465            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_logchl_diat', & 
     466               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     467            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_logchl_diat',    & 
     468               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     469               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     470               &                    lfpindegs, llnightav ) 
     471         ENDIF 
     472 
     473         IF (ln_surf_logchl_nondiat) THEN 
     474            jtype = jtype + 1 
     475            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_logchl_nondiat', & 
     476               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     477            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_logchl_nondiat', & 
     478               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     479               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     480               &                    lfpindegs, llnightav ) 
     481         ENDIF 
     482 
     483         IF (ln_surf_logchl_dino) THEN 
     484            jtype = jtype + 1 
     485            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_logchl_dino', & 
     486               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     487            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_logchl_dino',    & 
     488               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     489               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     490               &                    lfpindegs, llnightav ) 
     491         ENDIF 
     492 
     493         IF (ln_surf_logchl_micro) THEN 
     494            jtype = jtype + 1 
     495            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_logchl_micro', & 
     496               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     497            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_logchl_micro',   & 
     498               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     499               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     500               &                    lfpindegs, llnightav ) 
     501         ENDIF 
     502 
     503         IF (ln_surf_logchl_nano) THEN 
     504            jtype = jtype + 1 
     505            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_logchl_nano', & 
     506               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     507            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_logchl_nano',    & 
     508               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     509               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     510               &                    lfpindegs, llnightav ) 
     511         ENDIF 
     512 
     513         IF (ln_surf_logchl_pico) THEN 
     514            jtype = jtype + 1 
     515            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_logchl_pico', & 
     516               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     517            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_logchl_pico',    & 
     518               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     519               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     520               &                    lfpindegs, llnightav ) 
     521         ENDIF 
     522 
     523         IF (ln_surf_chl_total) THEN 
     524            jtype = jtype + 1 
     525            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_chl_total', & 
     526               &                   cn_logchlfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     527            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_chl_total',      & 
     528               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE.,    & 
     529               &                    n2dintsurf, ravglamscl, ravgphiscl,       & 
     530               &                    lfpindegs, llnightav ) 
     531         ENDIF 
     532 
     533         IF (ln_surf_spm) THEN 
     534            jtype = jtype + 1 
     535            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_spm', & 
     536               &                   cn_spmfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     537            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_spm',         & 
    415538               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE., & 
    416539               &                    n2dintsurf, ravglamscl, ravgphiscl,    & 
     
    418541         ENDIF 
    419542 
    420          IF (ln_spm) THEN 
    421             jtype = jtype + 1 
    422             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'spm   ', & 
    423                &                   cn_spmfbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    424             CALL obs_setinterpopts( nsurftypes, jtype, 'spm   ',         & 
     543         IF (ln_surf_fco2) THEN 
     544            jtype = jtype + 1 
     545            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_fco2', & 
     546               &                   cn_fco2fbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
     547            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_fco2',        & 
    425548               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE., & 
    426549               &                    n2dintsurf, ravglamscl, ravgphiscl,    & 
     
    428551         ENDIF 
    429552 
    430          IF (ln_fco2) THEN 
    431             jtype = jtype + 1 
    432             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'fco2  ', & 
    433                &                   cn_fco2fbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    434             CALL obs_setinterpopts( nsurftypes, jtype, 'fco2  ',         & 
    435                &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE., & 
    436                &                    n2dintsurf, ravglamscl, ravgphiscl,    & 
    437                &                    lfpindegs, llnightav ) 
    438          ENDIF 
    439  
    440          IF (ln_pco2) THEN 
    441             jtype = jtype + 1 
    442             CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'pco2  ', & 
     553         IF (ln_surf_pco2) THEN 
     554            jtype = jtype + 1 
     555            CALL obs_settypefiles( nsurftypes, jpmaxnfiles, jtype, 'surf_pco2', & 
    443556               &                   cn_pco2fbfiles, ifilessurf, cobstypessurf, clsurffiles ) 
    444             CALL obs_setinterpopts( nsurftypes, jtype, 'pco2  ',         & 
     557            CALL obs_setinterpopts( nsurftypes, jtype, 'surf_pco2',        & 
    445558               &                    nn_2dint, -1, 0., 0., .TRUE., .FALSE., & 
    446559               &                    n2dintsurf, ravglamscl, ravgphiscl,    & 
     
    793906               ENDIF 
    794907 
    795             CASE('logchl') 
     908            CASE('surf_logchl_total') 
    796909#if defined key_hadocc 
    797                zsurfvar(:,:) = HADOCC_CHL(:,:,1)    ! (not log) chlorophyll from HadOCC 
     910               ! Surface chlorophyll from HadOCC 
     911               zsurfvar(:,:) = HADOCC_CHL(:,:,1) 
    798912#elif defined key_medusa && defined key_foam_medusa 
    799913               ! Add non-diatom and diatom surface chlorophyll from MEDUSA 
    800914               zsurfvar(:,:) = trn(:,:,1,jpchn) + trn(:,:,1,jpchd) 
    801915#elif defined key_fabm 
    802                chl_3d(:,:,:) = fabm_get_bulk_diagnostic_data(model, jp_fabmdia_chltot) 
    803                zsurfvar(:,:) = chl_3d(:,:,1) 
     916               ! Add all surface chlorophyll groups from ERSEM 
     917               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl1) + trn(:,:,1,jp_fabm_chl2) + & 
     918                  &            trn(:,:,1,jp_fabm_chl3) + trn(:,:,1,jp_fabm_chl4) 
    804919#else 
    805                CALL ctl_stop( ' Trying to run logchl observation operator', & 
     920               CALL ctl_stop( ' Trying to run surf_logchl_total observation operator', & 
    806921                  &           ' but no biogeochemical model appears to have been defined' ) 
    807922#endif 
     
    815930                  zsurfmask(:,:) = 0 
    816931               END WHERE 
    817             CASE('spm') 
     932 
     933            CASE('surf_logchl_diat') 
     934#if defined key_hadocc 
     935               CALL ctl_stop( ' Trying to run surf_logchl_diat observation operator', & 
     936                  &           ' but HadOCC does not explicitly simulate diatoms' ) 
     937#elif defined key_medusa && defined key_foam_medusa 
     938               ! Diatom surface chlorophyll from MEDUSA 
     939               zsurfvar(:,:) = trn(:,:,1,jpchd) 
     940#elif defined key_fabm 
     941               ! Diatom surface chlorophyll from ERSEM 
     942               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl1) 
     943#else 
     944               CALL ctl_stop( ' Trying to run surf_logchl_diat observation operator', & 
     945                  &           ' but no biogeochemical model appears to have been defined' ) 
     946#endif 
     947               zsurfmask(:,:) = tmask(:,:,1)         ! create a special mask to exclude certain things 
     948               ! Take the log10 where we can, otherwise exclude 
     949               tiny = 1.0e-20 
     950               WHERE(zsurfvar(:,:) > tiny .AND. zsurfvar(:,:) /= obfillflt ) 
     951                  zsurfvar(:,:)  = LOG10(zsurfvar(:,:)) 
     952               ELSEWHERE 
     953                  zsurfvar(:,:)  = obfillflt 
     954                  zsurfmask(:,:) = 0 
     955               END WHERE 
     956 
     957            CASE('surf_logchl_nondiat') 
     958#if defined key_hadocc 
     959               CALL ctl_stop( ' Trying to run surf_logchl_nondiat observation operator', & 
     960                  &           ' but HadOCC does not explicitly simulate non-diatoms' ) 
     961#elif defined key_medusa && defined key_foam_medusa 
     962               ! Non-diatom surface chlorophyll from MEDUSA 
     963               zsurfvar(:,:) = trn(:,:,1,jpchn) 
     964#elif defined key_fabm 
     965               ! Add all non-diatom surface chlorophyll groups from ERSEM 
     966               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl2) + & 
     967                  &            trn(:,:,1,jp_fabm_chl3) + trn(:,:,1,jp_fabm_chl4) 
     968#else 
     969               CALL ctl_stop( ' Trying to run surf_logchl_nondiat observation operator', & 
     970                  &           ' but no biogeochemical model appears to have been defined' ) 
     971#endif 
     972               zsurfmask(:,:) = tmask(:,:,1)         ! create a special mask to exclude certain things 
     973               ! Take the log10 where we can, otherwise exclude 
     974               tiny = 1.0e-20 
     975               WHERE(zsurfvar(:,:) > tiny .AND. zsurfvar(:,:) /= obfillflt ) 
     976                  zsurfvar(:,:)  = LOG10(zsurfvar(:,:)) 
     977               ELSEWHERE 
     978                  zsurfvar(:,:)  = obfillflt 
     979                  zsurfmask(:,:) = 0 
     980               END WHERE 
     981 
     982            CASE('surf_logchl_dino') 
     983#if defined key_hadocc 
     984               CALL ctl_stop( ' Trying to run surf_logchl_dino observation operator', & 
     985                  &           ' but HadOCC does not explicitly simulate dinoflagellates' ) 
     986#elif defined key_medusa && defined key_foam_medusa 
     987               CALL ctl_stop( ' Trying to run surf_logchl_dino observation operator', & 
     988                  &           ' but MEDUSA does not explicitly simulate dinoflagellates' ) 
     989#elif defined key_fabm 
     990               ! Dinoflagellate surface chlorophyll from ERSEM 
     991               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl4) 
     992#else 
     993               CALL ctl_stop( ' Trying to run surf_logchl_dino observation operator', & 
     994                  &           ' but no biogeochemical model appears to have been defined' ) 
     995#endif 
     996               zsurfmask(:,:) = tmask(:,:,1)         ! create a special mask to exclude certain things 
     997               ! Take the log10 where we can, otherwise exclude 
     998               tiny = 1.0e-20 
     999               WHERE(zsurfvar(:,:) > tiny .AND. zsurfvar(:,:) /= obfillflt ) 
     1000                  zsurfvar(:,:)  = LOG10(zsurfvar(:,:)) 
     1001               ELSEWHERE 
     1002                  zsurfvar(:,:)  = obfillflt 
     1003                  zsurfmask(:,:) = 0 
     1004               END WHERE 
     1005 
     1006            CASE('surf_logchl_micro') 
     1007#if defined key_hadocc 
     1008               CALL ctl_stop( ' Trying to run surf_logchl_micro observation operator', & 
     1009                  &           ' but HadOCC does not explicitly simulate microphytoplankton' ) 
     1010#elif defined key_medusa && defined key_foam_medusa 
     1011               CALL ctl_stop( ' Trying to run surf_logchl_micro observation operator', & 
     1012                  &           ' but MEDUSA does not explicitly simulate microphytoplankton' ) 
     1013#elif defined key_fabm 
     1014               ! Add diatom and dinoflagellate surface chlorophyll from ERSEM 
     1015               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl1) + trn(:,:,1,jp_fabm_chl4) 
     1016#else 
     1017               CALL ctl_stop( ' Trying to run surf_logchl_micro observation operator', & 
     1018                  &           ' but no biogeochemical model appears to have been defined' ) 
     1019#endif 
     1020               zsurfmask(:,:) = tmask(:,:,1)         ! create a special mask to exclude certain things 
     1021               ! Take the log10 where we can, otherwise exclude 
     1022               tiny = 1.0e-20 
     1023               WHERE(zsurfvar(:,:) > tiny .AND. zsurfvar(:,:) /= obfillflt ) 
     1024                  zsurfvar(:,:)  = LOG10(zsurfvar(:,:)) 
     1025               ELSEWHERE 
     1026                  zsurfvar(:,:)  = obfillflt 
     1027                  zsurfmask(:,:) = 0 
     1028               END WHERE 
     1029 
     1030            CASE('surf_logchl_nano') 
     1031#if defined key_hadocc 
     1032               CALL ctl_stop( ' Trying to run surf_logchl_nano observation operator', & 
     1033                  &           ' but HadOCC does not explicitly simulate nanophytoplankton' ) 
     1034#elif defined key_medusa && defined key_foam_medusa 
     1035               CALL ctl_stop( ' Trying to run surf_logchl_nano observation operator', & 
     1036                  &           ' but MEDUSA does not explicitly simulate nanophytoplankton' ) 
     1037#elif defined key_fabm 
     1038               ! Nanophytoplankton surface chlorophyll from ERSEM 
     1039               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl2) 
     1040#else 
     1041               CALL ctl_stop( ' Trying to run surf_logchl_nano observation operator', & 
     1042                  &           ' but no biogeochemical model appears to have been defined' ) 
     1043#endif 
     1044               zsurfmask(:,:) = tmask(:,:,1)         ! create a special mask to exclude certain things 
     1045               ! Take the log10 where we can, otherwise exclude 
     1046               tiny = 1.0e-20 
     1047               WHERE(zsurfvar(:,:) > tiny .AND. zsurfvar(:,:) /= obfillflt ) 
     1048                  zsurfvar(:,:)  = LOG10(zsurfvar(:,:)) 
     1049               ELSEWHERE 
     1050                  zsurfvar(:,:)  = obfillflt 
     1051                  zsurfmask(:,:) = 0 
     1052               END WHERE 
     1053 
     1054            CASE('surf_logchl_pico') 
     1055#if defined key_hadocc 
     1056               CALL ctl_stop( ' Trying to run surf_logchl_pico observation operator', & 
     1057                  &           ' but HadOCC does not explicitly simulate picophytoplankton' ) 
     1058#elif defined key_medusa && defined key_foam_medusa 
     1059               CALL ctl_stop( ' Trying to run surf_logchl_pico observation operator', & 
     1060                  &           ' but MEDUSA does not explicitly simulate picophytoplankton' ) 
     1061#elif defined key_fabm 
     1062               ! Picophytoplankton surface chlorophyll from ERSEM 
     1063               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl3) 
     1064#else 
     1065               CALL ctl_stop( ' Trying to run surf_logchl_pico observation operator', & 
     1066                  &           ' but no biogeochemical model appears to have been defined' ) 
     1067#endif 
     1068               zsurfmask(:,:) = tmask(:,:,1)         ! create a special mask to exclude certain things 
     1069               ! Take the log10 where we can, otherwise exclude 
     1070               tiny = 1.0e-20 
     1071               WHERE(zsurfvar(:,:) > tiny .AND. zsurfvar(:,:) /= obfillflt ) 
     1072                  zsurfvar(:,:)  = LOG10(zsurfvar(:,:)) 
     1073               ELSEWHERE 
     1074                  zsurfvar(:,:)  = obfillflt 
     1075                  zsurfmask(:,:) = 0 
     1076               END WHERE 
     1077 
     1078            CASE('surf_chl_total') 
     1079#if defined key_hadocc 
     1080               ! Surface chlorophyll from HadOCC 
     1081               zsurfvar(:,:) = HADOCC_CHL(:,:,1) 
     1082#elif defined key_medusa && defined key_foam_medusa 
     1083               ! Add non-diatom and diatom surface chlorophyll from MEDUSA 
     1084               zsurfvar(:,:) = trn(:,:,1,jpchn) + trn(:,:,1,jpchd) 
     1085#elif defined key_fabm 
     1086               ! Add all surface chlorophyll groups from ERSEM 
     1087               zsurfvar(:,:) = trn(:,:,1,jp_fabm_chl1) + trn(:,:,1,jp_fabm_chl2) + & 
     1088                  &            trn(:,:,1,jp_fabm_chl3) + trn(:,:,1,jp_fabm_chl4) 
     1089#else 
     1090               CALL ctl_stop( ' Trying to run surf_chl_total observation operator', & 
     1091                  &           ' but no biogeochemical model appears to have been defined' ) 
     1092#endif 
     1093               zsurfmask(:,:) = tmask(:,:,1)         ! create a special mask to exclude certain things 
     1094 
     1095            CASE('surf_spm') 
    8181096#if defined key_spm 
    8191097               zsurfvar(:,:) = 0.0 
     
    8251103                  &           ' but no spm model appears to have been defined' ) 
    8261104#endif 
    827             CASE('fco2') 
     1105 
     1106            CASE('surf_fco2') 
    8281107#if defined key_hadocc 
    8291108               zsurfvar(:,:) = HADOCC_FCO2(:,:)    ! fCO2 from HadOCC 
     
    8641143                  &           ' but no biogeochemical model appears to have been defined' ) 
    8651144#endif 
    866             CASE('pco2') 
     1145 
     1146            CASE('surf_pco2') 
    8671147#if defined key_hadocc 
    8681148               zsurfvar(:,:) = HADOCC_PCO2(:,:)    ! pCO2 from HadOCC 
     
    12021482       &                   ifiles      ! Out appended number of files for this type 
    12031483 
    1204     CHARACTER(len=6), INTENT(IN) :: ctypein  
     1484    CHARACTER(len=25), INTENT(IN) :: ctypein  
    12051485    CHARACTER(len=128), DIMENSION(jpmaxnfiles), INTENT(IN) :: & 
    12061486       &                   cfilestype  ! In list of files for this obs type 
    1207     CHARACTER(len=6), DIMENSION(ntypes), INTENT(INOUT) :: & 
     1487    CHARACTER(len=25), DIMENSION(ntypes), INTENT(INOUT) :: & 
    12081488       &                   cobstypes   ! Out appended list of obs types 
    12091489    CHARACTER(len=128), DIMENSION(ntypes, jpmaxnfiles), INTENT(INOUT) :: & 
     
    12511531    LOGICAL, INTENT(IN)  :: lfp_indegs_type    !T=> footprint in degrees, F=> in metres 
    12521532    LOGICAL, INTENT(IN)  :: lavnight_type      !T=> obs represent night time average 
    1253     CHARACTER(len=6), INTENT(IN) :: ctypein  
     1533    CHARACTER(len=25), INTENT(IN) :: ctypein  
    12541534 
    12551535    INTEGER, DIMENSION(ntypes), INTENT(INOUT) :: & 
  • branches/UKMO/dev_r5518_obs_oper_update_bgc3d/NEMOGCM/NEMO/OPA_SRC/OBS/obs_write.F90

    r8223 r8687  
    8383      TYPE(obfbdata) :: fbdata 
    8484      CHARACTER(LEN=40) :: clfname 
    85       CHARACTER(LEN=10) :: clfiletype 
     85      CHARACTER(LEN=27) :: clfiletype 
    8686      INTEGER :: ilevel 
    8787      INTEGER :: jvar 
     
    320320      TYPE(obfbdata) :: fbdata 
    321321      CHARACTER(LEN=40) :: clfname         ! netCDF filename 
    322       CHARACTER(LEN=10) :: clfiletype 
     322      CHARACTER(LEN=27) :: clfiletype 
    323323      CHARACTER(LEN=12), PARAMETER :: cpname = 'obs_wri_surf' 
    324324      INTEGER :: jo 
     
    441441         END DO 
    442442 
    443       CASE('LOGCHL','LogChl','logchl') 
    444  
    445          CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
    446             &                 1 + iadd, iext, .TRUE. ) 
    447  
    448          clfiletype = 'logchlfb' 
    449          fbdata%cname(1)      = surfdata%cvars(1) 
    450          fbdata%coblong(1)    = 'logchl concentration' 
     443      CASE('SURF_LOGCHL_TOTAL','LOGCHL','LogChl','logchl') 
     444 
     445         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     446            &                 1 + iadd, iext, .TRUE. ) 
     447 
     448         clfiletype = 'surf_logchl_totalfb' 
     449         fbdata%cname(1)      = surfdata%cvars(1) 
     450         fbdata%coblong(1)    = 'Surface total log10(chlorophyll)' 
     451         fbdata%cobunit(1)    = 'log10(mg/m3)' 
     452         DO je = 1, iext 
     453            fbdata%cextname(je) = pext%cdname(je) 
     454            fbdata%cextlong(je) = pext%cdlong(je,1) 
     455            fbdata%cextunit(je) = pext%cdunit(je,1) 
     456         END DO 
     457         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
     458         fbdata%caddunit(1,1) = 'log10(mg/m3)' 
     459         fbdata%cgrid(1)      = 'T' 
     460         DO ja = 1, iadd 
     461            fbdata%caddname(1+ja) = padd%cdname(ja) 
     462            fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
     463            fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     464         END DO 
     465 
     466      CASE('SURF_LOGCHL_DIAT') 
     467 
     468         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     469            &                 1 + iadd, iext, .TRUE. ) 
     470 
     471         clfiletype = 'surf_logchl_diatfb' 
     472         fbdata%cname(1)      = surfdata%cvars(1) 
     473         fbdata%coblong(1)    = 'Surface diatom log10(chlorophyll)' 
     474         fbdata%cobunit(1)    = 'log10(mg/m3)' 
     475         DO je = 1, iext 
     476            fbdata%cextname(je) = pext%cdname(je) 
     477            fbdata%cextlong(je) = pext%cdlong(je,1) 
     478            fbdata%cextunit(je) = pext%cdunit(je,1) 
     479         END DO 
     480         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
     481         fbdata%caddunit(1,1) = 'log10(mg/m3)' 
     482         fbdata%cgrid(1)      = 'T' 
     483         DO ja = 1, iadd 
     484            fbdata%caddname(1+ja) = padd%cdname(ja) 
     485            fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
     486            fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     487         END DO 
     488 
     489      CASE('SURF_LOGCHL_NONDIAT') 
     490 
     491         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     492            &                 1 + iadd, iext, .TRUE. ) 
     493 
     494         clfiletype = 'surf_logchl_nondiatfb' 
     495         fbdata%cname(1)      = surfdata%cvars(1) 
     496         fbdata%coblong(1)    = 'Surface non-diatom log10(chlorophyll)' 
     497         fbdata%cobunit(1)    = 'log10(mg/m3)' 
     498         DO je = 1, iext 
     499            fbdata%cextname(je) = pext%cdname(je) 
     500            fbdata%cextlong(je) = pext%cdlong(je,1) 
     501            fbdata%cextunit(je) = pext%cdunit(je,1) 
     502         END DO 
     503         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
     504         fbdata%caddunit(1,1) = 'log10(mg/m3)' 
     505         fbdata%cgrid(1)      = 'T' 
     506         DO ja = 1, iadd 
     507            fbdata%caddname(1+ja) = padd%cdname(ja) 
     508            fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
     509            fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     510         END DO 
     511 
     512      CASE('SURF_LOGCHL_DINO') 
     513 
     514         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     515            &                 1 + iadd, iext, .TRUE. ) 
     516 
     517         clfiletype = 'surf_logchl_dinofb' 
     518         fbdata%cname(1)      = surfdata%cvars(1) 
     519         fbdata%coblong(1)    = 'Surface dinoflagellate log10(chlorophyll)' 
     520         fbdata%cobunit(1)    = 'log10(mg/m3)' 
     521         DO je = 1, iext 
     522            fbdata%cextname(je) = pext%cdname(je) 
     523            fbdata%cextlong(je) = pext%cdlong(je,1) 
     524            fbdata%cextunit(je) = pext%cdunit(je,1) 
     525         END DO 
     526         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
     527         fbdata%caddunit(1,1) = 'log10(mg/m3)' 
     528         fbdata%cgrid(1)      = 'T' 
     529         DO ja = 1, iadd 
     530            fbdata%caddname(1+ja) = padd%cdname(ja) 
     531            fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
     532            fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     533         END DO 
     534 
     535      CASE('SURF_LOGCHL_MICRO') 
     536 
     537         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     538            &                 1 + iadd, iext, .TRUE. ) 
     539 
     540         clfiletype = 'surf_logchl_microfb' 
     541         fbdata%cname(1)      = surfdata%cvars(1) 
     542         fbdata%coblong(1)    = 'Surface microphytoplankton log10(chlorophyll)' 
     543         fbdata%cobunit(1)    = 'log10(mg/m3)' 
     544         DO je = 1, iext 
     545            fbdata%cextname(je) = pext%cdname(je) 
     546            fbdata%cextlong(je) = pext%cdlong(je,1) 
     547            fbdata%cextunit(je) = pext%cdunit(je,1) 
     548         END DO 
     549         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
     550         fbdata%caddunit(1,1) = 'log10(mg/m3)' 
     551         fbdata%cgrid(1)      = 'T' 
     552         DO ja = 1, iadd 
     553            fbdata%caddname(1+ja) = padd%cdname(ja) 
     554            fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
     555            fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     556         END DO 
     557 
     558      CASE('SURF_LOGCHL_NANO') 
     559 
     560         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     561            &                 1 + iadd, iext, .TRUE. ) 
     562 
     563         clfiletype = 'surf_logchl_nanofb' 
     564         fbdata%cname(1)      = surfdata%cvars(1) 
     565         fbdata%coblong(1)    = 'Surface nanophytoplankton log10(chlorophyll)' 
     566         fbdata%cobunit(1)    = 'log10(mg/m3)' 
     567         DO je = 1, iext 
     568            fbdata%cextname(je) = pext%cdname(je) 
     569            fbdata%cextlong(je) = pext%cdlong(je,1) 
     570            fbdata%cextunit(je) = pext%cdunit(je,1) 
     571         END DO 
     572         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
     573         fbdata%caddunit(1,1) = 'log10(mg/m3)' 
     574         fbdata%cgrid(1)      = 'T' 
     575         DO ja = 1, iadd 
     576            fbdata%caddname(1+ja) = padd%cdname(ja) 
     577            fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
     578            fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     579         END DO 
     580 
     581      CASE('SURF_LOGCHL_PICO') 
     582 
     583         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     584            &                 1 + iadd, iext, .TRUE. ) 
     585 
     586         clfiletype = 'surf_logchl_picofb' 
     587         fbdata%cname(1)      = surfdata%cvars(1) 
     588         fbdata%coblong(1)    = 'Surface picophytoplankton log10(chlorophyll)' 
     589         fbdata%cobunit(1)    = 'log10(mg/m3)' 
     590         DO je = 1, iext 
     591            fbdata%cextname(je) = pext%cdname(je) 
     592            fbdata%cextlong(je) = pext%cdlong(je,1) 
     593            fbdata%cextunit(je) = pext%cdunit(je,1) 
     594         END DO 
     595         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
     596         fbdata%caddunit(1,1) = 'log10(mg/m3)' 
     597         fbdata%cgrid(1)      = 'T' 
     598         DO ja = 1, iadd 
     599            fbdata%caddname(1+ja) = padd%cdname(ja) 
     600            fbdata%caddlong(1+ja,1) = padd%cdlong(ja,1) 
     601            fbdata%caddunit(1+ja,1) = padd%cdunit(ja,1) 
     602         END DO 
     603 
     604      CASE('SURF_CHL_TOTAL') 
     605 
     606         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     607            &                 1 + iadd, iext, .TRUE. ) 
     608 
     609         clfiletype = 'surf_chl_totalfb' 
     610         fbdata%cname(1)      = surfdata%cvars(1) 
     611         fbdata%coblong(1)    = 'Surface total chlorophyll' 
    451612         fbdata%cobunit(1)    = 'mg/m3' 
    452613         DO je = 1, iext 
     
    455616            fbdata%cextunit(je) = pext%cdunit(je,1) 
    456617         END DO 
    457          fbdata%caddlong(1,1) = 'Model interpolated LOGCHL' 
     618         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
    458619         fbdata%caddunit(1,1) = 'mg/m3' 
    459620         fbdata%cgrid(1)      = 'T' 
     
    464625         END DO 
    465626 
    466       CASE('SPM','Spm','spm') 
    467  
    468          CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
    469             &                 1 + iadd, iext, .TRUE. ) 
    470  
    471          clfiletype = 'spmfb' 
    472          fbdata%cname(1)      = surfdata%cvars(1) 
    473          fbdata%coblong(1)    = 'spm' 
     627      CASE('SURF_SPM') 
     628 
     629         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     630            &                 1 + iadd, iext, .TRUE. ) 
     631 
     632         clfiletype = 'surf_spmfb' 
     633         fbdata%cname(1)      = surfdata%cvars(1) 
     634         fbdata%coblong(1)    = 'Surface suspended particulate matter' 
    474635         fbdata%cobunit(1)    = 'g/m3' 
    475636         DO je = 1, iext 
     
    478639            fbdata%cextunit(je) = pext%cdunit(je,1) 
    479640         END DO 
    480          fbdata%caddlong(1,1) = 'Model interpolated spm' 
     641         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
    481642         fbdata%caddunit(1,1) = 'g/m3' 
    482643         fbdata%cgrid(1)      = 'T' 
     
    487648         END DO 
    488649 
    489       CASE('FCO2','fCO2','fco2') 
    490  
    491          CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
    492             &                 1 + iadd, iext, .TRUE. ) 
    493  
    494          clfiletype = 'fco2fb' 
    495          fbdata%cname(1)      = surfdata%cvars(1) 
    496          fbdata%coblong(1)    = 'fco2' 
     650      CASE('SURF_FCO2','FCO2','fCO2','fco2') 
     651 
     652         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     653            &                 1 + iadd, iext, .TRUE. ) 
     654 
     655         clfiletype = 'surf_fco2fb' 
     656         fbdata%cname(1)      = surfdata%cvars(1) 
     657         fbdata%coblong(1)    = 'Surface fugacity of carbon dioxide' 
    497658         fbdata%cobunit(1)    = 'uatm' 
    498659         DO je = 1, iext 
     
    501662            fbdata%cextunit(je) = pext%cdunit(je,1) 
    502663         END DO 
    503          fbdata%caddlong(1,1) = 'Model interpolated fco2' 
     664         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
    504665         fbdata%caddunit(1,1) = 'uatm' 
    505666         fbdata%cgrid(1)      = 'T' 
     
    510671         END DO 
    511672 
    512       CASE('PCO2','pCO2','pco2') 
    513  
    514          CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
    515             &                 1 + iadd, iext, .TRUE. ) 
    516  
    517          clfiletype = 'pco2fb' 
    518          fbdata%cname(1)      = surfdata%cvars(1) 
    519          fbdata%coblong(1)    = 'pco2' 
     673      CASE('SURF_PCO2') 
     674 
     675         CALL alloc_obfbdata( fbdata, 1, surfdata%nsurf, 1, & 
     676            &                 1 + iadd, iext, .TRUE. ) 
     677 
     678         clfiletype = 'surf_pco2fb' 
     679         fbdata%cname(1)      = surfdata%cvars(1) 
     680         fbdata%coblong(1)    = 'Surface partial pressure of carbon dioxide' 
    520681         fbdata%cobunit(1)    = 'uatm' 
    521682         DO je = 1, iext 
     
    524685            fbdata%cextunit(je) = pext%cdunit(je,1) 
    525686         END DO 
    526          fbdata%caddlong(1,1) = 'Model interpolated pco2' 
     687         fbdata%caddlong(1,1) = 'Model interpolated ' // TRIM(surfdata%cvars(1)) 
    527688         fbdata%caddunit(1,1) = 'uatm' 
    528689         fbdata%cgrid(1)      = 'T' 
Note: See TracChangeset for help on using the changeset viewer.