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 8723 for branches/2017 – NEMO

Changeset 8723 for branches/2017


Ignore:
Timestamp:
2017-11-16T13:18:57+01:00 (6 years ago)
Author:
mattmartin
Message:

Commit changes to obs operator to work with SST bias correction and with the horizontal averaging operator.

Location:
branches/2017/dev_r8657_UKMO_OBSoper/NEMOGCM
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8657_UKMO_OBSoper/NEMOGCM/CONFIG/SHARED/namelist_ref

    r8599 r8723  
    11501150   ln_sla      = .false.             ! Logical switch for SLA observations 
    11511151   ln_sst      = .false.             ! Logical switch for SST observations 
     1152   ln_sss      = .false.             ! Logical swithc for SSS observations 
    11521153   ln_sic      = .false.             ! Logical switch for Sea Ice observations 
    11531154   ln_vel3d    = .false.             ! Logical switch for velocity observations 
    11541155   ln_altbias  = .false.             ! Logical switch for altimeter bias correction 
     1156   ln_sstbias  = .false.             ! Logical switch for SST bias correction 
    11551157   ln_nea      = .false.             ! Logical switch for rejection of observations near land 
    11561158   ln_grid_global = .true.           ! Logical switch for global distribution of observations 
     
    11591161   ln_s_at_t   = .false.             ! Logical switch for computing model S at T obs if not there 
    11601162   ln_sstnight = .false.             ! Logical switch for calculating night-time average for SST obs 
     1163   ln_sla_fp_indegs = .true.         ! Logical for SLA: T=> averaging footprint is in degrees, F=> in metres 
     1164   ln_sst_fp_indegs = .true.         ! Logical for SST: T=> averaging footprint is in degrees, F=> in metres 
     1165   ln_sss_fp_indegs = .true.         ! Logical for SSS: T=> averaging footprint is in degrees, F=> in metres 
     1166   ln_sic_fp_indegs = .true.         ! Logical for SIC: T=> averaging footprint is in degrees, F=> in metres 
    11611167! All of the *files* variables below are arrays. Use namelist_cfg to add more files 
    11621168   cn_profbfiles = 'profiles_01.nc'  ! Profile feedback input observation file names 
    11631169   cn_slafbfiles = 'sla_01.nc'       ! SLA feedback input observation file names 
    11641170   cn_sstfbfiles = 'sst_01.nc'       ! SST feedback input observation file names 
     1171   cn_sssfbfiles = 'sss_01.nc'       ! SSS feedback input observation file names 
    11651172   cn_sicfbfiles = 'sic_01.nc'       ! SIC feedback input observation file names 
    11661173   cn_velfbfiles = 'vel_01.nc'       ! Velocity feedback input observation file names 
    11671174   cn_altbiasfile = 'altbias.nc'     ! Altimeter bias input file name 
     1175   cn_sstbiasfiles = 'sstbias.nc'    ! SST bias input file name 
    11681176   cn_gridsearchfile='gridsearch.nc' ! Grid search file name 
    11691177   rn_gridsearchres = 0.5            ! Grid search resolution 
     1178   rn_mdtcorr  = 1.61                ! MDT  correction 
     1179   rn_mdtcutoff = 65.0               ! MDT cutoff for computed correction 
    11701180   rn_dobsini  = 00010101.000000     ! Initial date in window YYYYMMDD.HHMMSS 
    11711181   rn_dobsend  = 00010102.000000     ! Final date in window YYYYMMDD.HHMMSS 
    1172    nn_1dint    = 0                   ! Type of vertical interpolation method 
    1173    nn_2dint    = 0                   ! Type of horizontal interpolation method 
     1182   rn_sla_avglamscl = 0.             ! E/W diameter of SLA observation footprint (metres/degrees) 
     1183   rn_sla_avgphiscl = 0.             ! N/S diameter of SLA observation footprint (metres/degrees) 
     1184   rn_sst_avglamscl = 0.             ! E/W diameter of SST observation footprint (metres/degrees) 
     1185   rn_sst_avgphiscl = 0.             ! N/S diameter of SST observation footprint (metres/degrees) 
     1186   rn_sss_avglamscl = 0.             ! E/W diameter of SSS observation footprint (metres/degrees) 
     1187   rn_sss_avgphiscl = 0.             ! N/S diameter of SSS observation footprint (metres/degrees) 
     1188   rn_sic_avglamscl = 0.             ! E/W diameter of SIC observation footprint (metres/degrees) 
     1189   rn_sic_avgphiscl = 0.             ! N/S diameter of SIC observation footprint (metres/degrees) 
     1190   nn_1dint = 0                      ! Type of vertical interpolation method 
     1191   nn_2dint = 0                      ! Default horizontal interpolation method 
     1192   nn_2dint_sla = 0                  ! Horizontal interpolation method for SLA 
     1193   nn_2dint_sst = 0                  ! Horizontal interpolation method for SST 
     1194   nn_2dint_sss = 0                  ! Horizontal interpolation method for SSS 
     1195   nn_2dint_sic = 0                  ! Horizontal interpolation method for SIC 
    11741196   nn_msshc    = 0                   ! MSSH correction scheme 
    1175    rn_mdtcorr  = 1.61                ! MDT  correction 
    1176    rn_mdtcutoff = 65.0               ! MDT cutoff for computed correction 
    11771197   nn_profdavtypes = -1              ! Profile daily average types - array 
    1178    ln_sstbias  = .false.             ! 
    1179    cn_sstbias_files = 'sstbias.nc'   ! 
    11801198/ 
    11811199!----------------------------------------------------------------------- 
  • branches/2017/dev_r8657_UKMO_OBSoper/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r8667 r8723  
    4848   LOGICAL, PUBLIC :: ln_diaobs   !: Logical switch for the obs operator 
    4949   LOGICAL :: ln_sstnight         !: Logical switch for night mean SST obs 
    50     
     50   LOGICAL :: ln_sla_fp_indegs    !: T=> SLA obs footprint size specified in degrees, F=> in metres 
     51   LOGICAL :: ln_sst_fp_indegs    !: T=> SST obs footprint size specified in degrees, F=> in metres 
     52   LOGICAL :: ln_sss_fp_indegs    !: T=> SSS obs footprint size specified in degrees, F=> in metres 
     53   LOGICAL :: ln_sic_fp_indegs    !: T=> sea-ice obs footprint size specified in degrees, F=> in metres 
     54 
     55   REAL(wp) :: rn_sla_avglamscl !: E/W diameter of SLA observation footprint (metres) 
     56   REAL(wp) :: rn_sla_avgphiscl !: N/S diameter of SLA observation footprint (metres) 
     57   REAL(wp) :: rn_sst_avglamscl !: E/W diameter of SST observation footprint (metres) 
     58   REAL(wp) :: rn_sst_avgphiscl !: N/S diameter of SST observation footprint (metres) 
     59   REAL(wp) :: rn_sss_avglamscl !: E/W diameter of SSS observation footprint (metres) 
     60   REAL(wp) :: rn_sss_avgphiscl !: N/S diameter of SSS observation footprint (metres) 
     61   REAL(wp) :: rn_sic_avglamscl !: E/W diameter of sea-ice observation footprint (metres) 
     62   REAL(wp) :: rn_sic_avgphiscl !: N/S diameter of sea-ice observation footprint (metres) 
     63 
    5164   INTEGER :: nn_1dint       !: Vertical interpolation method 
    52    INTEGER :: nn_2dint       !: Horizontal interpolation method 
     65   INTEGER :: nn_2dint       !: Default horizontal interpolation method 
     66   INTEGER :: nn_2dint_sla   !: SLA horizontal interpolation method  
     67   INTEGER :: nn_2dint_sst   !: SST horizontal interpolation method  
     68   INTEGER :: nn_2dint_sss   !: SSS horizontal interpolation method  
     69   INTEGER :: nn_2dint_sic   !: Seaice horizontal interpolation method  
    5370   INTEGER, DIMENSION(imaxavtypes) :: & 
    5471      & nn_profdavtypes      !: Profile data types representing a daily average 
     
    6178      & nextrprof, &         !: Number of profile extra variables 
    6279      & nextrsurf            !: Number of surface extra variables 
    63    INTEGER, PUBLIC, ALLOCATABLE, DIMENSION(:) :: sstbias_type !SST bias type     
     80   INTEGER, DIMENSION(:), ALLOCATABLE :: & 
     81      & n2dintsurf           !: Interpolation option for surface variables 
     82   REAL(wp), DIMENSION(:), ALLOCATABLE :: & 
     83      & ravglamscl, &        !: E/W diameter of averaging footprint for surface variables 
     84      & ravgphiscl           !: N/S diameter of averaging footprint for surface variables 
     85   LOGICAL, DIMENSION(:), ALLOCATABLE :: & 
     86      & lfpindegs, &         !: T=> surface obs footprint size specified in degrees, F=> in metres 
     87      & llnightav            !: Logical for calculating night-time averages 
     88 
    6489   TYPE(obs_surf), PUBLIC, POINTER, DIMENSION(:) :: & 
    6590      & surfdata, &          !: Initial surface data 
     
    116141         & cn_profbfiles, &      ! T/S profile input filenames 
    117142         & cn_sstfbfiles, &      ! Sea surface temperature input filenames 
     143         & cn_sssfbfiles, &      ! Sea surface salinity input filenames 
    118144         & cn_slafbfiles, &      ! Sea level anomaly input filenames 
    119145         & cn_sicfbfiles, &      ! Seaice concentration input filenames 
    120146         & cn_velfbfiles, &      ! Velocity profile input filenames 
    121          & cn_sstbias_files      ! SST bias input filenames 
     147         & cn_sstbiasfiles      ! SST bias input filenames 
    122148      CHARACTER(LEN=128) :: & 
    123149         & cn_altbiasfile        ! Altimeter bias input filename 
     
    130156      LOGICAL :: ln_sla          ! Logical switch for sea level anomalies  
    131157      LOGICAL :: ln_sst          ! Logical switch for sea surface temperature 
     158      LOGICAL :: ln_sss          ! Logical switch for sea surface salinity 
    132159      LOGICAL :: ln_sic          ! Logical switch for sea ice concentration 
    133160      LOGICAL :: ln_vel3d        ! Logical switch for velocity (u,v) obs 
    134161      LOGICAL :: ln_nea          ! Logical switch to remove obs near land 
    135162      LOGICAL :: ln_altbias      ! Logical switch for altimeter bias 
    136       LOGICAL :: ln_sstbias     !: Logical switch for bias corection of SST  
     163      LOGICAL :: ln_sstbias      ! Logical switch for bias corection of SST  
    137164      LOGICAL :: ln_ignmis       ! Logical switch for ignoring missing files 
    138165      LOGICAL :: ln_s_at_t       ! Logical switch to compute model S at T obs 
     166      LOGICAL :: ln_bound_reject ! Logical to remove obs near boundaries in LAMs. 
    139167      LOGICAL :: llvar1          ! Logical for profile variable 1 
    140168      LOGICAL :: llvar2          ! Logical for profile variable 1 
    141       LOGICAL :: llnightav       ! Logical for calculating night-time averages 
    142169      LOGICAL, DIMENSION(jpmaxnfiles) :: lmask ! Used for finding number of sstbias files 
    143170 
     
    189216      ! Read namelist parameters 
    190217      !----------------------------------------------------------------------- 
    191        
    192       !Initalise all values in namelist arrays 
    193       ALLOCATE(sstbias_type(jpmaxnfiles)) 
    194218      ! Some namelist arrays need initialising 
    195219      cn_profbfiles(:) = '' 
     
    199223      cn_velfbfiles(:) = '' 
    200224      cn_sssfbfiles(:)    = '' 
    201       cn_sstbias_files(:) = '' 
     225      cn_sstbiasfiles(:) = '' 
    202226      nn_profdavtypes(:) = -1 
    203227 
     
    262286      IF (ln_sstbias) THEN  
    263287         lmask(:) = .FALSE.  
    264          WHERE (cn_sstbias_files(:) /= '') lmask(:) = .TRUE.  
     288         WHERE (cn_sstbiasfiles(:) /= '') lmask(:) = .TRUE.  
    265289         jnumsstbias = COUNT(lmask)  
    266290         lmask(:) = .FALSE.  
     
    463487            nvarssurf(jtype) = 1 
    464488            nextrsurf(jtype) = 0 
    465             llnightav = .FALSE. 
     489            llnightav(jtype) = .FALSE. 
    466490            IF ( TRIM(cobstypessurf(jtype)) == 'sla' ) nextrsurf(jtype) = 2 
    467             IF ( TRIM(cobstypessurf(jtype)) == 'sst' ) llnightav = ln_sstnight 
     491            IF ( TRIM(cobstypessurf(jtype)) == 'sst' ) llnightav(jtype) = ln_sstnight 
    468492 
    469493            !Read in surface obs types 
     
    581605         & zgphi1,    &            ! Model latitudes for prof variable 1 
    582606         & zgphi2                  ! Model latitudes for prof variable 2 
    583       LOGICAL :: llnightav        ! Logical for calculating night-time average 
    584607 
    585608      !Allocate local work arrays 
     
    971994   END SUBROUTINE fin_date 
    972995    
     996    SUBROUTINE obs_settypefiles( ntypes, jpmaxnfiles, jtype, ctypein, & 
     997       &                         cfilestype, ifiles, cobstypes, cfiles ) 
     998 
     999    INTEGER, INTENT(IN) :: ntypes      ! Total number of obs types 
     1000    INTEGER, INTENT(IN) :: jpmaxnfiles ! Maximum number of files allowed for each type 
     1001    INTEGER, INTENT(IN) :: jtype       ! Index of the current type of obs 
     1002    INTEGER, DIMENSION(ntypes), INTENT(INOUT) :: & 
     1003       &                   ifiles      ! Out appended number of files for this type 
     1004 
     1005    CHARACTER(len=6), INTENT(IN) :: ctypein  
     1006    CHARACTER(len=128), DIMENSION(jpmaxnfiles), INTENT(IN) :: & 
     1007       &                   cfilestype  ! In list of files for this obs type 
     1008    CHARACTER(len=6), DIMENSION(ntypes), INTENT(INOUT) :: & 
     1009       &                   cobstypes   ! Out appended list of obs types 
     1010    CHARACTER(len=128), DIMENSION(ntypes, jpmaxnfiles), INTENT(INOUT) :: & 
     1011       &                   cfiles      ! Out appended list of files for all types 
     1012 
     1013    !Local variables 
     1014    INTEGER :: jfile 
     1015 
     1016    cfiles(jtype,:) = cfilestype(:) 
     1017    cobstypes(jtype) = ctypein 
     1018    ifiles(jtype) = 0 
     1019    DO jfile = 1, jpmaxnfiles 
     1020       IF ( trim(cfiles(jtype,jfile)) /= '' ) & 
     1021                 ifiles(jtype) = ifiles(jtype) + 1 
     1022    END DO 
     1023 
     1024    IF ( ifiles(jtype) == 0 ) THEN 
     1025         CALL ctl_stop( 'Logical for observation type '//TRIM(ctypein)//   & 
     1026            &           ' set to true but no files available to read' ) 
     1027    ENDIF 
     1028 
     1029    IF(lwp) THEN     
     1030       WRITE(numout,*) '             '//cobstypes(jtype)//' input observation file names:' 
     1031       DO jfile = 1, ifiles(jtype) 
     1032          WRITE(numout,*) '                '//TRIM(cfiles(jtype,jfile)) 
     1033       END DO 
     1034    ENDIF 
     1035 
     1036    END SUBROUTINE obs_settypefiles 
     1037 
     1038    SUBROUTINE obs_setinterpopts( ntypes, jtype, ctypein,             & 
     1039               &                  n2dint_default, n2dint_type,        & 
     1040               &                  ravglamscl_type, ravgphiscl_type,   & 
     1041               &                  lfp_indegs_type, lavnight_type,     & 
     1042               &                  n2dint, ravglamscl, ravgphiscl,     & 
     1043               &                  lfpindegs, lavnight ) 
     1044 
     1045    INTEGER, INTENT(IN)  :: ntypes             ! Total number of obs types 
     1046    INTEGER, INTENT(IN)  :: jtype              ! Index of the current type of obs 
     1047    INTEGER, INTENT(IN)  :: n2dint_default     ! Default option for interpolation type 
     1048    INTEGER, INTENT(IN)  :: n2dint_type        ! Option for interpolation type 
     1049    REAL(wp), INTENT(IN) :: & 
     1050       &                    ravglamscl_type, & !E/W diameter of obs footprint for this type 
     1051       &                    ravgphiscl_type    !N/S diameter of obs footprint for this type 
     1052    LOGICAL, INTENT(IN)  :: lfp_indegs_type    !T=> footprint in degrees, F=> in metres 
     1053    LOGICAL, INTENT(IN)  :: lavnight_type      !T=> obs represent night time average 
     1054    CHARACTER(len=6), INTENT(IN) :: ctypein  
     1055 
     1056    INTEGER, DIMENSION(ntypes), INTENT(INOUT) :: & 
     1057       &                    n2dint  
     1058    REAL(wp), DIMENSION(ntypes), INTENT(INOUT) :: & 
     1059       &                    ravglamscl, ravgphiscl 
     1060    LOGICAL, DIMENSION(ntypes), INTENT(INOUT) :: & 
     1061       &                    lfpindegs, lavnight 
     1062 
     1063    lavnight(jtype) = lavnight_type 
     1064 
     1065    IF ( (n2dint_type >= 1) .AND. (n2dint_type <= 6) ) THEN 
     1066       n2dint(jtype) = n2dint_type 
     1067    ELSE 
     1068       n2dint(jtype) = n2dint_default 
     1069    ENDIF 
     1070 
     1071    ! For averaging observation footprints set options for size of footprint  
     1072    IF ( (n2dint(jtype) > 4) .AND. (n2dint(jtype) <= 6) ) THEN 
     1073       IF ( ravglamscl_type > 0._wp ) THEN 
     1074          ravglamscl(jtype) = ravglamscl_type 
     1075       ELSE 
     1076          CALL ctl_stop( 'Incorrect value set for averaging footprint '// & 
     1077                         'scale (ravglamscl) for observation type '//TRIM(ctypein) )       
     1078       ENDIF 
     1079 
     1080       IF ( ravgphiscl_type > 0._wp ) THEN 
     1081          ravgphiscl(jtype) = ravgphiscl_type 
     1082       ELSE 
     1083          CALL ctl_stop( 'Incorrect value set for averaging footprint '// & 
     1084                         'scale (ravgphiscl) for observation type '//TRIM(ctypein) )       
     1085       ENDIF 
     1086 
     1087       lfpindegs(jtype) = lfp_indegs_type  
     1088 
     1089    ENDIF 
     1090 
     1091    ! Write out info  
     1092    IF(lwp) THEN 
     1093       IF ( n2dint(jtype) <= 4 ) THEN 
     1094          WRITE(numout,*) '             '//TRIM(ctypein)// & 
     1095             &            ' model counterparts will be interpolated horizontally' 
     1096       ELSE IF ( n2dint(jtype) <= 6 ) THEN 
     1097          WRITE(numout,*) '             '//TRIM(ctypein)// & 
     1098             &            ' model counterparts will be averaged horizontally' 
     1099          WRITE(numout,*) '             '//'    with E/W scale: ',ravglamscl(jtype) 
     1100          WRITE(numout,*) '             '//'    with N/S scale: ',ravgphiscl(jtype) 
     1101          IF ( lfpindegs(jtype) ) THEN 
     1102              WRITE(numout,*) '             '//'    (in degrees)' 
     1103          ELSE 
     1104              WRITE(numout,*) '             '//'    (in metres)' 
     1105          ENDIF 
     1106       ENDIF 
     1107    ENDIF 
     1108 
     1109    END SUBROUTINE obs_setinterpopts 
     1110 
    9731111END MODULE diaobs 
  • branches/2017/dev_r8657_UKMO_OBSoper/NEMOGCM/NEMO/OPA_SRC/OBS/obs_oper.F90

    r8667 r8723  
    2626      & obs_int_z1d,    & 
    2727      & obs_int_z1d_spl 
    28    USE obs_const,  ONLY :     & 
    29       & obfillflt      ! Fillvalue    
     28   USE obs_const,  ONLY :    &    ! Obs fill value 
     29      & obfillflt 
    3030   USE dom_oce,       ONLY : & 
    3131      & glamt, glamf, & 
    32       & gphit, gphif, &  
    33       & gdept_n, gdept_0  
    34    USE lib_mpp,       ONLY : & 
     32      & gphit, gphif 
     33   USE lib_mpp,       ONLY : &    ! Warning and stopping routines 
    3534      & ctl_warn, ctl_stop 
     35   USE sbcdcy,        ONLY : &    ! For calculation of where it is night-time 
     36      & sbc_dcy, nday_qsr 
    3637   USE obs_grid,      ONLY : &  
    3738      & obs_level_search      
    38    USE sbcdcy,        ONLY : &    ! For calculation of where it is night-time 
    39       & sbc_dcy, nday_qsr 
    4039 
    4140   IMPLICIT NONE 
     
    5857CONTAINS 
    5958 
     59 
    6060   SUBROUTINE obs_prof_opt( prodatqc, kt, kpi, kpj, kpk,          & 
    6161      &                     kit000, kdaystp,                      & 
    62       &                     pvar1, pvar2, pgdept, pmask1, pmask2, & 
     62      &                     pvar1, pvar2, pgdept, pgdepw,         & 
     63      &                     pmask1, pmask2,                       &   
    6364      &                     plam1, plam2, pphi1, pphi2,           & 
    6465      &                     k1dint, k2dint, kdailyavtypes ) 
     
    111112      !!      ! 07-03 (K. Mogensen) General handling of profiles 
    112113      !!      ! 15-02 (M. Martin) Combined routine for all profile types 
     114      !!      ! 17-02 (M. Martin) Include generalised vertical coordinate changes 
    113115      !!----------------------------------------------------------------------- 
    114116 
     
    140142         & pphi1,    &               ! Model latitudes for variable 1 
    141143         & pphi2                     ! Model latitudes for variable 2 
    142       REAL(KIND=wp), INTENT(IN), DIMENSION(kpk) :: & 
    143          & pgdept                    ! Model array of depth levels 
     144      REAL(KIND=wp), INTENT(IN), DIMENSION(kpi,kpj,kpk) :: &  
     145         & pgdept, &                 ! Model array of depth T levels  
     146         & pgdepw                    ! Model array of depth W levels  
    144147      INTEGER, DIMENSION(imaxavtypes), OPTIONAL :: & 
    145148         & kdailyavtypes             ! Types for daily averages 
     
    156159      INTEGER ::   iend 
    157160      INTEGER ::   iobs 
     161      INTEGER ::   iin, ijn, ikn, ik   ! looping indices over interpolation nodes  
     162      INTEGER ::   inum_obs 
    158163      INTEGER, DIMENSION(imaxavtypes) :: & 
    159164         & idailyavtypes 
     
    163168         & igrdj1, & 
    164169         & igrdj2 
     170      INTEGER, ALLOCATABLE, DIMENSION(:) :: iv_indic 
     171 
    165172      REAL(KIND=wp) :: zlam 
    166173      REAL(KIND=wp) :: zphi 
     
    171178         & zobsk,    & 
    172179         & zobs2k 
    173       REAL(KIND=wp), DIMENSION(2,2,kpk) :: & 
     180      REAL(KIND=wp), DIMENSION(2,2,1) :: & 
    174181         & zweig1, & 
    175          & zweig2 
     182         & zweig2, & 
     183         & zweig 
    176184      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: & 
    177185         & zmask1, & 
    178186         & zmask2, & 
    179          & zint1, & 
    180          & zint2, & 
    181          & zinm1, & 
    182          & zinm2 
     187         & zint1,  & 
     188         & zint2,  & 
     189         & zinm1,  & 
     190         & zinm2,  & 
     191         & zgdept, &  
     192         & zgdepw 
    183193      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: & 
    184194         & zglam1, & 
     
    186196         & zgphi1, & 
    187197         & zgphi2 
     198      REAL(KIND=wp), DIMENSION(1) :: zmsk_1, zmsk_2    
     199      REAL(KIND=wp), DIMENSION(:,:,:), ALLOCATABLE :: interp_corner 
     200 
    188201      LOGICAL :: ld_dailyav 
    189202 
     
    266279         & zmask1(2,2,kpk,ipro),  & 
    267280         & zmask2(2,2,kpk,ipro),  & 
    268          & zint1(2,2,kpk,ipro),  & 
    269          & zint2(2,2,kpk,ipro)   & 
     281         & zint1(2,2,kpk,ipro),   & 
     282         & zint2(2,2,kpk,ipro),   & 
     283         & zgdept(2,2,kpk,ipro),  &  
     284         & zgdepw(2,2,kpk,ipro)   &  
    270285         & ) 
    271286 
     
    411426               ENDIF !idayend 
    412427 
    413             ELSE  
     428            ELSE    
    414429 
    415430               ! Point data  
     
    476491 
    477492                        ENDIF  
     493 
    478494                     ENDDO depth_loop1  
    479495      
  • branches/2017/dev_r8657_UKMO_OBSoper/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r8667 r8723  
    6161      !!---------------------------------------------------------------------- 
    6262      !! * Modules used 
    63       USE domstp              ! Domain: set the time-step 
    6463      USE par_oce             ! Ocean parameters 
    6564      USE dom_oce, ONLY       :   glamt, gphit, tmask, nproc   ! Geographical information 
     
    262261      !!---------------------------------------------------------------------- 
    263262      !! * Modules used 
    264       USE domstp              ! Domain: set the time-step 
    265263      USE par_oce             ! Ocean parameters 
    266264      USE dom_oce, ONLY : &   ! Geographical information 
Note: See TracChangeset for help on using the changeset viewer.