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/branches/UKMO/NEMO_4.0.4_generic_obs/src/OCE/OBS – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.4_generic_obs/src/OCE/OBS/obs_readmdt.F90 @ 15285

Last change on this file since 15285 was 15285, checked in by dford, 3 years ago

Some bug fixes.

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