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 12380 for branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC/OBS/obs_oper.F90 – NEMO

Ignore:
Timestamp:
2020-02-13T15:10:57+01:00 (4 years ago)
Author:
dcarneir
Message:

Updating obs_oper with obs_oper version in the apps trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC/OBS/obs_oper.F90

    r11932 r12380  
    546546      &                     kit000, kdaystp, psurf, pclim, psurfmask,   & 
    547547      &                     k2dint, ldnightav, plamscl, pphiscl, & 
    548       &                     lindegrees ) 
     548      &                     lindegrees, kmeanstp ) 
    549549 
    550550      !!----------------------------------------------------------------------- 
     
    596596      INTEGER, INTENT(IN) :: kdaystp   ! Number of time steps per day 
    597597      INTEGER, INTENT(IN) :: k2dint    ! Horizontal interpolation type (see header) 
     598      INTEGER, INTENT(IN), OPTIONAL :: & 
     599                             kmeanstp  ! Number of time steps for the time meaning 
     600                                       ! Averaging is triggered if present and greater than one                     
    598601      REAL(wp), INTENT(IN), DIMENSION(kpi,kpj) :: & 
    599602         & psurf,  &                   ! Model surface field 
     
    617620      INTEGER :: imodi, imodj 
    618621      INTEGER :: idayend 
     622      INTEGER :: imeanend 
    619623      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: & 
    620624         & igrdi,   & 
     
    629633      REAL(wp), DIMENSION(1) :: zext, zobsmask, zclm 
    630634      REAL(wp) :: zdaystp 
     635      REAL(wp) :: zmeanstp 
    631636      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: & 
    632637         & zweig,  & 
     
    645650         & zouttmp, & 
    646651         & zmeanday    ! to compute model sst in region of 24h daylight (pole) 
     652 
     653      LOGICAL :: l_timemean 
    647654          
    648655      !------------------------------------------------------------------------ 
     
    653660      isurf = surfdataqc%nsstp(inrc) 
    654661 
     662      l_timemean = .FALSE. 
     663      IF ( PRESENT( kmeanstp ) ) THEN 
     664         IF ( kmeanstp > 1 ) l_timemean = .TRUE. 
     665      ENDIF 
     666 
    655667      ! Work out the maximum footprint size for the  
    656668      ! interpolation/averaging in model grid-points - has to be even. 
    657669 
    658670      CALL obs_max_fpsize( k2dint, plamscl, pphiscl, lindegrees, psurfmask, imaxifp, imaxjfp ) 
     671 
     672 
     673      IF ( l_timemean ) THEN 
     674         ! Initialize time mean for first timestep 
     675         imeanend = MOD( kt - kit000 + 1, kmeanstp ) 
     676         IF (lwp) WRITE(numout,*) 'Obs time mean ', kt, kit000, kmeanstp, imeanend 
     677 
     678         ! Added kt == 0 test to catch restart case  
     679         IF ( ( imeanend == 1 ) .OR. ( kt == 0 ) ) THEN 
     680            IF (lwp) WRITE(numout,*) 'Reset surfdataqc%vdmean on time-step: ',kt 
     681            DO jj = 1, jpj 
     682               DO ji = 1, jpi 
     683                  surfdataqc%vdmean(ji,jj) = 0.0 
     684               END DO 
     685            END DO 
     686         ENDIF 
     687 
     688         ! On each time-step, increment the field for computing time mean 
     689         IF (lwp) WRITE(numout,*)'Accumulating surfdataqc%vdmean on time-step: ',kt 
     690         DO jj = 1, jpj 
     691            DO ji = 1, jpi 
     692               surfdataqc%vdmean(ji,jj) = surfdataqc%vdmean(ji,jj) & 
     693                  &                        + psurf(ji,jj) 
     694            END DO 
     695         END DO 
     696 
     697         ! Compute the time mean at the end of time period 
     698         IF ( imeanend == 0 ) THEN 
     699            zmeanstp = 1.0 / REAL( kmeanstp ) 
     700            IF (lwp) WRITE(numout,*)'Calculating surfdataqc%vdmean time mean on time-step: ',kt,' with weight: ',zmeanstp 
     701            DO jj = 1, jpj 
     702               DO ji = 1, jpi 
     703                  surfdataqc%vdmean(ji,jj) = surfdataqc%vdmean(ji,jj) & 
     704                     &                       * zmeanstp 
     705               END DO 
     706            END DO 
     707         ENDIF 
     708      ENDIF !l_timemean 
    659709 
    660710 
     
    774824      CALL obs_int_comm_2d( imaxifp, imaxjfp, isurf, kpi, kpj, & 
    775825         &                  igrdi, igrdj, psurfmask, zmask ) 
    776       CALL obs_int_comm_2d( imaxifp, imaxjfp, isurf, kpi, kpj, & 
    777          &                  igrdi, igrdj, psurf, zsurf ) 
     826 
     827      ! At the end of the averaging period get interpolated means 
     828      IF ( l_timemean ) THEN 
     829         IF ( imeanend == 0 ) THEN 
     830            ALLOCATE( zsurfm(imaxifp,imaxjfp,isurf) ) 
     831            IF (lwp) WRITE(numout,*)' Interpolating the time mean values on time step: ',kt 
     832            CALL obs_int_comm_2d( imaxifp, imaxjfp, isurf, kpi, kpj, & 
     833               &                  igrdi, igrdj, surfdataqc%vdmean(:,:), zsurfm ) 
     834         ENDIF 
     835      ELSE 
     836         CALL obs_int_comm_2d( imaxifp, imaxjfp, isurf, kpi, kpj, & 
     837            &                  igrdi, igrdj, psurf, zsurf ) 
     838      ENDIF 
    778839 
    779840      IF ( k2dint > 4 ) THEN          
     
    827888         zphi = surfdataqc%rphi(jobs) 
    828889 
    829          IF ( ldnightav .AND. idayend == 0 ) THEN 
    830             ! Night-time averaged data 
     890         IF (( ldnightav .AND. idayend == 0 ) .OR. (l_timemean .AND. imeanend == 0)) THEN 
     891            ! Night-time or N=kmeanstp timestep averaged data 
    831892            zsurftmp(:,:,iobs) = zsurfm(:,:,iobs) 
    832893         ELSE 
     
    834895         ENDIF 
    835896 
    836          IF ( k2dint <= 4 ) THEN 
    837  
    838             ! Get weights to interpolate the model value to the observation point 
    839             CALL obs_int_h2d_init( 1, 1, k2dint, zlam, zphi,         & 
    840                &                   zglam(:,:,iobs), zgphi(:,:,iobs), & 
    841                &                   zmask(:,:,iobs), zweig, zobsmask ) 
    842  
    843             ! Interpolate the model value to the observation point  
    844             CALL obs_int_h2d( 1, 1, zweig, zsurftmp(:,:,iobs), zext ) 
    845  
    846             IF ( surfdataqc%lclim ) THEN   
    847                CALL obs_int_h2d( 1, 1, zweig, zclim(:,:,iobs), zclm ) 
     897         IF (   ( .NOT. l_timemean ) .OR. &  
     898             &  ( l_timemean .AND. imeanend == 0) ) THEN 
     899            IF ( k2dint <= 4 ) THEN 
     900 
     901               ! Get weights to interpolate the model value to the observation point 
     902               CALL obs_int_h2d_init( 1, 1, k2dint, zlam, zphi,         & 
     903                  &                   zglam(:,:,iobs), zgphi(:,:,iobs), & 
     904                  &                   zmask(:,:,iobs), zweig, zobsmask ) 
     905 
     906               ! Interpolate the model value to the observation point  
     907               CALL obs_int_h2d( 1, 1, zweig, zsurftmp(:,:,iobs), zext ) 
     908 
     909               IF ( surfdataqc%lclim ) THEN   
     910                  CALL obs_int_h2d( 1, 1, zweig, zclim(:,:,iobs), zclm ) 
     911               ENDIF 
     912 
     913 
     914            ELSE 
     915 
     916               ! Get weights to average the model SLA to the observation footprint 
     917               CALL obs_avg_h2d_init( 1, 1, imaxifp, imaxjfp, k2dint, zlam,  zphi, & 
     918                  &                   zglam(:,:,iobs), zgphi(:,:,iobs), & 
     919                  &                   zglamf(:,:,iobs), zgphif(:,:,iobs), & 
     920                  &                   zmask(:,:,iobs), plamscl, pphiscl, & 
     921                  &                   lindegrees, zweig, zobsmask ) 
     922 
     923               ! Average the model SST to the observation footprint 
     924               CALL obs_avg_h2d( 1, 1, imaxifp, imaxjfp, & 
     925                  &              zweig, zsurftmp(:,:,iobs),  zext ) 
     926 
     927               IF ( surfdataqc%lclim ) THEN   
     928                  CALL obs_avg_h2d( 1, 1, imaxifp, imaxjfp, & 
     929                     &              zweig, zclim(:,:,iobs),  zclm ) 
     930               ENDIF 
     931 
    848932            ENDIF 
    849933 
    850  
    851          ELSE 
    852  
    853             ! Get weights to average the model SLA to the observation footprint 
    854             CALL obs_avg_h2d_init( 1, 1, imaxifp, imaxjfp, k2dint, zlam,  zphi, & 
    855                &                   zglam(:,:,iobs), zgphi(:,:,iobs), & 
    856                &                   zglamf(:,:,iobs), zgphif(:,:,iobs), & 
    857                &                   zmask(:,:,iobs), plamscl, pphiscl, & 
    858                &                   lindegrees, zweig, zobsmask ) 
    859  
    860             ! Average the model SST to the observation footprint 
    861             CALL obs_avg_h2d( 1, 1, imaxifp, imaxjfp, & 
    862                &              zweig, zsurftmp(:,:,iobs),  zext ) 
    863  
    864             IF ( surfdataqc%lclim ) THEN   
    865                CALL obs_avg_h2d( 1, 1, imaxifp, imaxjfp, & 
    866                   &              zweig, zclim(:,:,iobs),  zclm ) 
     934            IF ( TRIM(surfdataqc%cvars(1)) == 'SLA' .AND. surfdataqc%nextra == 2 ) THEN 
     935               ! ... Remove the MDT from the SSH at the observation point to get the SLA 
     936               surfdataqc%rext(jobs,1) = zext(1) 
     937               surfdataqc%rmod(jobs,1) = surfdataqc%rext(jobs,1) - surfdataqc%rext(jobs,2) 
     938            ELSE 
     939               surfdataqc%rmod(jobs,1) = zext(1) 
    867940            ENDIF 
    868941 
    869          ENDIF 
    870  
    871          IF ( TRIM(surfdataqc%cvars(1)) == 'SLA' .AND. surfdataqc%nextra == 2 ) THEN 
    872             ! ... Remove the MDT from the SSH at the observation point to get the SLA 
    873             surfdataqc%rext(jobs,1) = zext(1) 
    874             surfdataqc%rmod(jobs,1) = surfdataqc%rext(jobs,1) - surfdataqc%rext(jobs,2) 
    875          ELSE 
    876             surfdataqc%rmod(jobs,1) = zext(1) 
     942            IF ( surfdataqc%lclim ) surfdataqc%rclm(jobs,1) = zclm(1) 
     943 
     944            IF ( zext(1) == obfillflt ) THEN 
     945               ! If the observation value is a fill value, set QC flag to bad 
     946               surfdataqc%nqc(jobs) = 4 
     947            ENDIF          
    877948         ENDIF 
    878949          
     
    900971            surfdataqc%nqc(jobs) = 4 
    901972         ENDIF 
    902  
     973          
    903974      END DO 
    904975 
     
    922993 
    923994      ! At the end of the day also deallocate night-time mean array 
    924       IF ( idayend == 0 .AND. ldnightav ) THEN 
     995      IF (( idayend == 0 .AND. ldnightav ) .OR. ( imeanend == 0 .AND. l_timemean )) THEN 
    925996         DEALLOCATE( & 
    926997            & zsurfm  & 
Note: See TracChangeset for help on using the changeset viewer.