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.
obs_readmdt.F90 in NEMO/trunk/src/OCE/OBS – NEMO

source: NEMO/trunk/src/OCE/OBS/obs_readmdt.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 9.9 KB
RevLine 
[2128]1MODULE obs_readmdt
2   !!======================================================================
3   !!                       ***  MODULE obs_readmdt  ***
4   !! Observation diagnostics: Read the MDT for SLA data (skeleton for now)
5   !!======================================================================
[2715]6   !! History :      ! 2007-03 (K. Mogensen) Initial skeleton version
7   !!                ! 2007-04 (E. Remy) migration and improvement from OPAVAR
8   !!----------------------------------------------------------------------
[2128]9
10   !!----------------------------------------------------------------------
[2715]11   !!   obs_rea_mdt    : Driver for reading MDT
12   !!   obs_offset_mdt : Remove the offset between the model MDT and the used one
[2128]13   !!----------------------------------------------------------------------
[2715]14   USE par_kind         ! Precision variables
15   USE par_oce          ! Domain parameters
16   USE in_out_manager   ! I/O manager
17   USE obs_surf_def     ! Surface observation definitions
18   USE obs_inter_sup    ! Interpolation support routines
19   USE obs_inter_h2d    ! 2D interpolation
20   USE obs_utils        ! Various observation tools
21   USE iom_nf90         ! IOM NetCDF
22   USE netcdf           ! NetCDF library
23   USE lib_mpp          ! MPP library
24   USE dom_oce, ONLY : &                  ! Domain variables
[5836]25      &                    tmask, tmask_i, e1e2t, gphit, glamt
[2715]26   USE obs_const, ONLY :   obfillflt      ! Fillvalue
[12377]27   USE oce      , ONLY :   ssh            ! Model variables
[2128]28
29   IMPLICIT NONE
30   PRIVATE
[2715]31   
[6140]32   PUBLIC   obs_rea_mdt     ! called by dia_obs_init
33   PUBLIC   obs_offset_mdt  ! called by obs_rea_mdt
[2128]34
[6140]35   INTEGER , PUBLIC :: nn_msshc    = 1         ! MDT correction scheme
36   REAL(wp), PUBLIC :: rn_mdtcorr   = 1.61_wp  ! User specified MDT correction
37   REAL(wp), PUBLIC :: rn_mdtcutoff = 65.0_wp  ! MDT cutoff for computed correction
[2128]38
[12377]39   !! * Substitutions
40#  include "do_loop_substitute.h90"
[2287]41   !!----------------------------------------------------------------------
[9598]42   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[2287]43   !! $Id$
[10068]44   !! Software governed by the CeCILL license (see ./LICENSE)
[2287]45   !!----------------------------------------------------------------------
[2128]46CONTAINS
47
[12377]48   SUBROUTINE obs_rea_mdt( sladata, k2dint, Kmm )
[2128]49      !!---------------------------------------------------------------------
50      !!
51      !!                   *** ROUTINE obs_rea_mdt ***
52      !!
53      !! ** Purpose : Read from file the MDT data (skeleton)
54      !!
55      !! ** Method  :
56      !!
57      !! ** Action  :
58      !!----------------------------------------------------------------------
59      USE iom
[2715]60      !
[6140]61      TYPE(obs_surf), INTENT(inout) ::   sladata   ! SLA data
62      INTEGER       , INTENT(in)    ::   k2dint    ! ?
[12377]63      INTEGER       , INTENT(in)    ::   Kmm       ! ?
[2715]64      !
65      CHARACTER(LEN=12), PARAMETER ::   cpname  = 'obs_rea_mdt'
66      CHARACTER(LEN=20), PARAMETER ::   mdtname = 'slaReferenceLevel.nc'
[2128]67
[2715]68      INTEGER ::   jobs                ! Obs loop variable
69      INTEGER ::   jpimdt, jpjmdt      ! Number of grid point in lat/lon for the MDT
70      INTEGER ::   iico, ijco          ! Grid point indicies
71      INTEGER ::   i_nx_id, i_ny_id, i_file_id, i_var_id, i_stat
72      INTEGER ::   nummdt
73      !
74      REAL(wp), DIMENSION(1)     ::   zext, zobsmask
75      REAL(wp), DIMENSION(2,2,1) ::   zweig
76      !
77      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   zmask, zmdtl, zglam, zgphi
78      INTEGER , DIMENSION(:,:,:), ALLOCATABLE ::   igrdi, igrdj
[3294]79      !
[9125]80      REAL(wp), DIMENSION(jpi,jpj) ::  z_mdt, mdtmask
[2715]81         
82      REAL(wp) :: zlam, zphi, zfill, zinfill    ! local scalar
83      !!----------------------------------------------------------------------
[2128]84
85      IF(lwp)WRITE(numout,*) 
[2715]86      IF(lwp)WRITE(numout,*) ' obs_rea_mdt : Read MDT for referencing altimeter anomalies'
[2128]87      IF(lwp)WRITE(numout,*) ' ------------- '
[6140]88      CALL FLUSH(numout)
[2128]89
[2715]90      CALL iom_open( mdtname, nummdt )       ! Open the file
91      !                                      ! Get the MDT data
92      CALL iom_get ( nummdt, jpdom_data, 'sossheig', z_mdt(:,:), 1 )
93      CALL iom_close(nummdt)                 ! Close the file
[2128]94     
95      ! Read in the fill value
96      zinfill = 0.0
97      i_stat = nf90_open( mdtname, nf90_nowrite, nummdt )
98      i_stat = nf90_inq_varid( nummdt, 'sossheig', i_var_id )
99      i_stat = nf90_get_att( nummdt, i_var_id, "_FillValue",zinfill)
100      zfill = zinfill
101      i_stat = nf90_close( nummdt )
102
[2715]103      ! setup mask based on tmask and MDT mask
104      ! set mask to 0 where the MDT is set to fillvalue
105      WHERE(z_mdt(:,:) /= zfill)   ;   mdtmask(:,:) = tmask(:,:,1)
106      ELSE WHERE                   ;   mdtmask(:,:) = 0
[2128]107      END WHERE
108
109      ! Remove the offset between the MDT used with the sla and the model MDT
[6140]110      IF( nn_msshc == 1 .OR. nn_msshc == 2 ) &
[12377]111         & CALL obs_offset_mdt( jpi, jpj, z_mdt, zfill, Kmm )
[2128]112
113      ! Intepolate the MDT already on the model grid at the observation point
114 
[6140]115      ALLOCATE( &
116         & igrdi(2,2,sladata%nsurf), &
117         & igrdj(2,2,sladata%nsurf), &
118         & zglam(2,2,sladata%nsurf), &
119         & zgphi(2,2,sladata%nsurf), &
120         & zmask(2,2,sladata%nsurf), &
121         & zmdtl(2,2,sladata%nsurf)  &
122         & )
[2128]123         
[6140]124      DO jobs = 1, sladata%nsurf
[2128]125
[6140]126         igrdi(1,1,jobs) = sladata%mi(jobs)-1
127         igrdj(1,1,jobs) = sladata%mj(jobs)-1
128         igrdi(1,2,jobs) = sladata%mi(jobs)-1
129         igrdj(1,2,jobs) = sladata%mj(jobs)
130         igrdi(2,1,jobs) = sladata%mi(jobs)
131         igrdj(2,1,jobs) = sladata%mj(jobs)-1
132         igrdi(2,2,jobs) = sladata%mi(jobs)
133         igrdj(2,2,jobs) = sladata%mj(jobs)
[2128]134
[6140]135      END DO
[2128]136
[6140]137      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, igrdi, igrdj, glamt  , zglam )
138      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, igrdi, igrdj, gphit  , zgphi )
139      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, igrdi, igrdj, mdtmask, zmask )
140      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, igrdi, igrdj, z_mdt  , zmdtl )
[2128]141
[6140]142      DO jobs = 1, sladata%nsurf
[2128]143           
[6140]144         zlam = sladata%rlam(jobs)
145         zphi = sladata%rphi(jobs)
[2128]146
[6140]147         CALL obs_int_h2d_init( 1, 1, k2dint, zlam, zphi,         &
148            &                   zglam(:,:,jobs), zgphi(:,:,jobs), &
149            &                   zmask(:,:,jobs), zweig, zobsmask )
[2128]150           
[6140]151         CALL obs_int_h2d( 1, 1, zweig, zmdtl(:,:,jobs),  zext )
[2128]152 
[6140]153         sladata%rext(jobs,2) = zext(1)
[2128]154
155! mark any masked data with a QC flag
[9023]156         IF( zobsmask(1) == 0 )   sladata%nqc(jobs) = IBSET(sladata%nqc(jobs),15)
[2128]157
158         END DO
159         
[6140]160      DEALLOCATE( &
161         & igrdi, &
162         & igrdj, &
163         & zglam, &
164         & zgphi, &
165         & zmask, &
166         & zmdtl  &
167         & )
[2128]168
[6140]169      IF(lwp)WRITE(numout,*) ' ------------- '
[2715]170      !
[2128]171   END SUBROUTINE obs_rea_mdt
172
[2715]173
[12377]174   SUBROUTINE obs_offset_mdt( kpi, kpj, mdt, zfill, Kmm )
[2128]175      !!---------------------------------------------------------------------
176      !!
177      !!                   *** ROUTINE obs_offset_mdt ***
178      !!
179      !! ** Purpose : Compute a correction term for the MDT on the model grid
180      !!             !!!!! IF it is on the model grid
181      !!
182      !! ** Method  : Compute the mean difference between the model and the
183      !!              used MDT and remove the offset.
184      !!
185      !! ** Action  :
186      !!----------------------------------------------------------------------
[6140]187      INTEGER, INTENT(IN) ::  kpi, kpj
[12377]188      INTEGER, INTENT(IN) ::  Kmm
[6140]189      REAL(wp), DIMENSION(kpi,kpj), INTENT(INOUT) ::   mdt     ! MDT used on the model grid
190      REAL(wp)                    , INTENT(IN   ) ::   zfill 
[2715]191      !
192      INTEGER  :: ji, jj
193      REAL(wp) :: zdxdy, zarea, zeta1, zeta2, zcorr_mdt, zcorr_bcketa, zcorr     ! local scalar
[9125]194      REAL(wp), DIMENSION(jpi,jpj) :: zpromsk
[2715]195      CHARACTER(LEN=14), PARAMETER ::   cpname = 'obs_offset_mdt'
196      !!----------------------------------------------------------------------
[2128]197
198      !  Initialize the local mask, for domain projection
199      !  Also exclude mdt points which are set to missing data
200
201      DO ji = 1, jpi
202        DO jj = 1, jpj
203           zpromsk(ji,jj) = tmask_i(ji,jj)
[6140]204           IF (    ( gphit(ji,jj) .GT.  rn_mdtcutoff ) &
205              &.OR.( gphit(ji,jj) .LT. -rn_mdtcutoff ) &
[2128]206              &.OR.( mdt(ji,jj) .EQ. zfill ) ) &
207              &        zpromsk(ji,jj) = 0.0
208        END DO
209      END DO 
210
[6140]211      ! Compute MSSH mean over [0,360] x [-rn_mdtcutoff,rn_mdtcutoff]
[2128]212
213      zarea = 0.0
214      zeta1 = 0.0
215      zeta2 = 0.0
216
[12377]217      DO_2D_11_11
218       zdxdy = e1e2t(ji,jj) * zpromsk(ji,jj)
219       zarea = zarea + zdxdy
220       zeta1 = zeta1 + mdt(ji,jj) * zdxdy
221       zeta2 = zeta2 + ssh(ji,jj,Kmm) * zdxdy
222      END_2D
[2128]223
[10425]224      CALL mpp_sum( 'obs_readmdt', zeta1 )
225      CALL mpp_sum( 'obs_readmdt', zeta2 )
226      CALL mpp_sum( 'obs_readmdt', zarea )
[2128]227     
[2715]228      zcorr_mdt    = zeta1 / zarea
229      zcorr_bcketa = zeta2 / zarea
[2128]230
231      !  Define correction term
232
233      zcorr = zcorr_mdt - zcorr_bcketa
234
235      !  Correct spatial mean of the MSSH
236
[6140]237      IF( nn_msshc == 1 )   mdt(:,:) = mdt(:,:) - zcorr 
[2128]238
239      ! User defined value : 1.6 m for the Rio MDT compared to ORCA2 MDT
240
[6140]241      IF( nn_msshc == 2 )   mdt(:,:) = mdt(:,:) - rn_mdtcorr
[2128]242
243      IF(lwp) THEN
244         WRITE(numout,*)
[6140]245         WRITE(numout,*) ' obs_readmdt : rn_mdtcutoff     = ', rn_mdtcutoff
[2128]246         WRITE(numout,*) ' -----------   zcorr_mdt     = ', zcorr_mdt
247         WRITE(numout,*) '               zcorr_bcketa  = ', zcorr_bcketa
248         WRITE(numout,*) '               zcorr         = ', zcorr
[6140]249         WRITE(numout,*) '               nn_msshc        = ', nn_msshc
[2128]250      ENDIF
251
[6140]252      IF ( nn_msshc == 0 ) WRITE(numout,*) '           MSSH correction is not applied'
253      IF ( nn_msshc == 1 ) WRITE(numout,*) '           MSSH correction is applied'
254      IF ( nn_msshc == 2 ) WRITE(numout,*) '           User defined MSSH correction' 
[2128]255
[2715]256      !
[2128]257   END SUBROUTINE obs_offset_mdt
258 
[2715]259   !!======================================================================
[2128]260END MODULE obs_readmdt
Note: See TracBrowser for help on using the repository browser.