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 6003 for branches – NEMO

Changeset 6003 for branches


Ignore:
Timestamp:
2015-12-04T17:03:23+01:00 (8 years ago)
Author:
timgraham
Message:

Fixes from last merge

Location:
branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/OBS
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r5998 r6003  
    6161      & nextrprof, &         !: Number of profile extra variables 
    6262      & nextrsurf            !: Number of surface extra variables 
    63    INTEGER, PUBLIC, ALLOCATABLE, DIMENSION(:),:: sstbias_type !SST bias type     
     63   INTEGER, PUBLIC, ALLOCATABLE, DIMENSION(:) :: sstbias_type !SST bias type     
    6464   TYPE(obs_surf), PUBLIC, POINTER, DIMENSION(:) :: & 
    6565      & surfdata, &          !: Initial surface data 
     
    120120         & cn_slafbfiles, &      ! Sea level anomaly input filenames 
    121121         & cn_sicfbfiles, &      ! Seaice concentration input filenames 
    122          & cn_velfbfiles         ! Velocity profile input filenames 
     122         & cn_velfbfiles, &      ! Velocity profile input filenames 
     123         & cn_sstbias_files      ! SST bias input filenames 
    123124      CHARACTER(LEN=128) :: & 
    124125         & cn_altbiasfile        ! Altimeter bias input filename 
    125          & cn_sstbias_files      ! Altimeter bias input filenames 
    126126      CHARACTER(len=128), DIMENSION(:,:), ALLOCATABLE :: & 
    127127         & clproffiles, &        ! Profile filenames 
     
    142142      LOGICAL :: llvar2          ! Logical for profile variable 1 
    143143      LOGICAL :: llnightav       ! Logical for calculating night-time averages 
     144      LOGICAL, DIMENSION(jpmaxnfiles) :: lmask ! Used for finding number of sstbias files 
    144145 
    145146      REAL(dp) :: rn_dobsini     ! Obs window start date YYYYMMDD.HHMMSS 
     
    166167         &            rn_dobsini, rn_dobsend, nn_1dint, nn_2dint,     & 
    167168         &            nn_msshc, rn_mdtcorr, rn_mdtcutoff,             & 
    168          &            nn_profdavtypes, ln_sstbias, sstbias_files 
    169  
    170       INTEGER :: jnumsstbias  !TG - Is this still needed 
     169         &            nn_profdavtypes, ln_sstbias, cn_sstbias_files 
     170 
     171      INTEGER :: jnumsstbias 
    171172      CALL wrk_alloc( jpi, jpj, zglam1 ) 
    172173      CALL wrk_alloc( jpi, jpj, zglam2 ) 
     
    181182       
    182183      !Initalise all values in namelist arrays 
    183       ALLOCATE(sstbias_type(jpmaxnumfiles)) 
     184      ALLOCATE(sstbias_type(jpmaxnfiles)) 
    184185      ! Some namelist arrays need initialising 
    185186      cn_profbfiles(:) = '' 
     
    220221      IF (ln_sstbias) THEN  
    221222         lmask(:) = .FALSE.  
    222          WHERE (sstbias_files(:) /= '') lmask(:) = .TRUE.  
     223         WHERE (cn_sstbias_files(:) /= '') lmask(:) = .TRUE.  
    223224         jnumsstbias = COUNT(lmask)  
    224225         lmask(:) = .FALSE.  
     
    467468               &               rn_dobsini, rn_dobsend, ln_ignmis, .FALSE., llnightav ) 
    468469          
     470          
     471            CALL obs_pre_surf( surfdata(jtype), surfdataqc(jtype), ln_nea ) 
     472 
     473            IF ( TRIM(cobstypessurf(jtype)) == 'sla' ) THEN 
     474               CALL obs_rea_mdt( surfdataqc(jtype), nn_2dint ) 
     475               IF ( ln_altbias ) CALL obs_rea_altbias ( surfdataqc(jtype), nn_2dint, cn_altbiasfile ) 
     476            ENDIF 
     477 
     478         END DO 
     479 
    469480         !Read in bias field and correct SST. 
    470481         IF ( ln_sstbias ) THEN 
     
    472483                                             "  but no bias"// & 
    473484                                             " files to read in")    
    474             CALL obs_app_sstbias( nsstsets, sstdatqc, n2dint, & 
    475                                   jnumsstbias, &  
    476                                   sstbias_files(1:jnumsstbias) ) 
     485!            CALL obs_app_sstbias( nsstsets, sstdatqc, nn_2dint, & 
     486!                                  jnumsstbias, cn_sstbias_files(1:jnumsstbias) ) 
    477487         ENDIF 
    478           
    479             CALL obs_pre_surf( surfdata(jtype), surfdataqc(jtype), ln_nea ) 
    480  
    481             IF ( TRIM(cobstypessurf(jtype)) == 'sla' ) THEN 
    482                CALL obs_rea_mdt( surfdataqc(jtype), nn_2dint ) 
    483                IF ( ln_altbias ) CALL obs_rea_altbias ( surfdataqc(jtype), nn_2dint, cn_altbiasfile ) 
    484             ENDIF 
    485  
    486          END DO 
     488 
    487489 
    488490         DEALLOCATE( ifilessurf, clsurffiles ) 
     
    526528      USE dom_oce, ONLY : &             ! Ocean space and time domain variables 
    527529#if defined key_vvl  
    528          & gdept_n,       & 
     530         & gdept_n        
    529531#else  
    530          & gdept_1d,      & 
     532         & gdept_1d       
    531533#endif                                         
    532534      USE phycst, ONLY : &              ! Physical constants 
     
    534536      USE oce, ONLY : &                 ! Ocean dynamics and tracers variables 
    535537         & tsn,  &              
    536          & un, vn,  & 
     538         & un, vn, & 
     539         & sshn   
    537540      USE phycst, ONLY : &         ! Physical constants 
    538541         & rday 
    539          & sshn 
    540542#if defined  key_lim3 
    541543      USE ice, ONLY : &            ! LIM3 Ice model variables 
     
    605607      !----------------------------------------------------------------------- 
    606608 
    607 <<<<<<< .working 
    608       !  - Temperature/salinity profiles 
    609       IF ( ln_t3d .OR. ln_s3d ) THEN 
    610          DO jprofset = 1, nprofsets 
    611             IF( ln_zco .OR. ln_zps ) THEN  
    612                IF ( ld_enact(jprofset) ) THEN  
    613                   CALL obs_pro_opt( prodatqc(jprofset),                     &  
    614                      &              kstp, jpi, jpj, jpk, nit000, idaystp,   &  
    615                      &              tsn(:,:,:,jp_tem), tsn(:,:,:,jp_sal),   &  
    616                      &              gdept_1d, tmask, n1dint, n2dint,        &  
    617                      &              kdailyavtypes = endailyavtypes )  
    618                ELSE  
    619                   CALL obs_pro_opt( prodatqc(jprofset),                     &  
    620                      &              kstp, jpi, jpj, jpk, nit000, idaystp,   &  
    621                      &              tsn(:,:,:,jp_tem), tsn(:,:,:,jp_sal),   &  
    622                      &              gdept_1d, tmask, n1dint, n2dint               )  
    623                ENDIF  
    624             ELSE 
    625                IF ( ld_enact(jprofset) ) THEN  
    626                   CALL obs_pro_sco_opt( prodatqc(jprofset),                 &  
    627                      &              kstp, jpi, jpj, jpk, nit000, idaystp,   &  
    628                      &              tsn(:,:,:,jp_tem), tsn(:,:,:,jp_sal),   &  
    629                      &              fsdept(:,:,:), fsdepw(:,:,:),           & 
    630                      &              tmask, n1dint, n2dint,   &  
    631                      &              kdailyavtypes = endailyavtypes )  
    632                ELSE  
    633                   CALL obs_pro_sco_opt( prodatqc(jprofset),                 &  
    634                      &              kstp, jpi, jpj, jpk, nit000, idaystp,   &  
    635                      &              tsn(:,:,:,jp_tem), tsn(:,:,:,jp_sal),   &  
    636                      &              fsdept(:,:,:), fsdepw(:,:,:),           & 
    637                      &              tmask, n1dint, n2dint )  
    638                ENDIF  
    639             ENDIF 
    640          END DO 
    641       ENDIF 
    642 ======= 
    643609      IF ( nproftypes > 0 ) THEN 
    644 >>>>>>> .merge-right.r5997 
    645610 
    646611         DO jtype = 1, nproftypes 
     
    675640                  &               nn_1dint, nn_2dint,                      & 
    676641                  &               kdailyavtypes = nn_profdavtypes ) 
    677             ELSE IF(TRIM(cobstypesprof(jtype)) == 'prof') 
     642            ELSE IF(TRIM(cobstypesprof(jtype)) == 'prof') THEN 
    678643               !TG - THIS NEEDS MODIFICATION TO MATCH SIMPLIFICATION 
    679                CALL obs_pro_sco_opt( prodatqc(jtype),                    &  
     644               CALL obs_pro_sco_opt( profdataqc(jtype),                    &  
    680645                  &              kstp, jpi, jpj, jpk, nit000, idaystp,   &  
    681646                  &              zprofvar1, zprofvar2,                   &  
     
    684649                  &              kdailyavtypes = nn_profdavtypes )  
    685650            ELSE 
    686                ctl_stop('DIA_OBS: Generalised vertical interpolation not'// & 
     651               CALL ctl_stop('DIA_OBS: Generalised vertical interpolation not'// & 
    687652                         'yet working for velocity date (turn off velocity observations') 
    688653            ENDIF 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/OBS/obs_oper.F90

    r5998 r6003  
    571571         & psn,    &    ! Model salinity field  
    572572         & ptmask       ! Land-sea mask  
    573       REAL(KIND=wp), INTENT(IN), DIMENSION(kpi,jpj,kpk) :: &  
     573      REAL(KIND=wp), INTENT(IN), DIMENSION(kpi,kpj,kpk) :: &  
    574574         & pgdept,  &    ! Model array of depth T levels     
    575575         & pgdepw       ! Model array of depth W levels  
     
    711711      zgdepw = 0.0 
    712712  
    713       CALL obs_int_comm_2d( 2, 2, ipro, igrdi, igrdj, glamt, zglam )  
    714       CALL obs_int_comm_2d( 2, 2, ipro, igrdi, igrdj, gphit, zgphi )  
    715       CALL obs_int_comm_3d( 2, 2, ipro, kpk, igrdi, igrdj, ptmask,zmask )  
    716       CALL obs_int_comm_3d( 2, 2, ipro, kpk, igrdi, igrdj, ptn,   zintt )  
    717       CALL obs_int_comm_3d( 2, 2, ipro, kpk, igrdi, igrdj, psn,   zints )  
    718       CALL obs_int_comm_3d( 2, 2, ipro, kpk, igrdi, igrdj, pgdept(:,:,:), &  
     713      CALL obs_int_comm_2d( 2, 2, ipro, kpi, kpj, igrdi, igrdj, glamt, zglam )  
     714      CALL obs_int_comm_2d( 2, 2, ipro, kpi, kpj, igrdi, igrdj, gphit, zgphi )  
     715      CALL obs_int_comm_3d( 2, 2, ipro, kpi, kpj, kpk, igrdi, igrdj, ptmask,zmask )  
     716      CALL obs_int_comm_3d( 2, 2, ipro, kpi, kpj, kpk, igrdi, igrdj, ptn,   zintt )  
     717      CALL obs_int_comm_3d( 2, 2, ipro, kpi, kpj, kpk, igrdi, igrdj, psn,   zints )  
     718      CALL obs_int_comm_3d( 2, 2, ipro, kpi, kpj, kpk, igrdi, igrdj, pgdept(:,:,:), &  
    719719        &                     zgdept )  
    720       CALL obs_int_comm_3d( 2, 2, ipro, kpk, igrdi, igrdj, pgdepw(:,:,:), &  
     720      CALL obs_int_comm_3d( 2, 2, ipro, kpi, kpj, kpk, igrdi, igrdj, pgdepw(:,:,:), &  
    721721        &                     zgdepw )  
    722722  
     
    729729            & )  
    730730  
    731          CALL obs_int_comm_3d( 2, 2, ipro, kpk, igrdi, igrdj, &  
     731         CALL obs_int_comm_3d( 2, 2, ipro, kpi, kpj, kpk, igrdi, igrdj, &  
    732732            &                  prodatqc%vdmean(:,:,:,1), zinmt )  
    733          CALL obs_int_comm_3d( 2, 2, ipro, kpk, igrdi, igrdj, &  
     733         CALL obs_int_comm_3d( 2, 2, ipro, kpi, kpj, kpk, igrdi, igrdj, &  
    734734            &                  prodatqc%vdmean(:,:,:,2), zinms )  
    735735  
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/OBS/obs_sstbias.F90

    r5992 r6003  
    170170            igrdj(2,2,jobs) = sstdata(jslano)%mj(jobs) 
    171171         END DO 
    172          CALL obs_int_comm_2d( 2, 2, sstdata(jslano)%nsurf, & 
     172         CALL obs_int_comm_2d( 2, 2, sstdata(jslano)%nsurf, jpi, jpj, & 
    173173            &                  igrdi, igrdj, glamt, zglam ) 
    174          CALL obs_int_comm_2d( 2, 2, sstdata(jslano)%nsurf, & 
     174         CALL obs_int_comm_2d( 2, 2, sstdata(jslano)%nsurf, jpi, jpj, & 
    175175            &                  igrdi, igrdj, gphit, zgphi ) 
    176          CALL obs_int_comm_2d( 2, 2, sstdata(jslano)%nsurf, & 
     176         CALL obs_int_comm_2d( 2, 2, sstdata(jslano)%nsurf, jpi, jpj, & 
    177177            &                  igrdi, igrdj, tmask(:,:,1), zmask ) 
    178178         DO jtype = 1, knumtypes 
     
    201201            END DO 
    202202                          
    203             CALL obs_int_comm_2d( 2, 2, inumtype, & 
     203            CALL obs_int_comm_2d( 2, 2, inumtype, jpi, jpj, & 
    204204                  &           igrdi_tmp(:,:,:), igrdj_tmp(:,:,:), & 
    205205                  &           z_sstbias(:,:,jtype), zbias(:,:,:) ) 
Note: See TracChangeset for help on using the changeset viewer.