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_read_altbias.F90 in NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/OBS – NEMO

source: NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/OBS/obs_read_altbias.F90 @ 10009

Last change on this file since 10009 was 10009, checked in by gm, 6 years ago

#1911 (ENHANCE-04): RK3 branch - step II.1 time-level dimension on ssh

  • Property svn:keywords set to Id
File size: 5.9 KB
Line 
1MODULE obs_read_altbias
2   !!======================================================================
3   !!                       ***  MODULE obs_readaltbias  ***
4   !! Observation diagnostics: Read the bias for SLA data
5   !!======================================================================
6
7   !!----------------------------------------------------------------------
8   !!   obs_rea_altbias : Driver for reading altimeter bias
9   !!----------------------------------------------------------------------
10
11   !! * Modules used   
12   USE par_kind, ONLY : &       ! Precision variables
13      & wp, &
14      & dp, &
15      & sp
16   USE par_oce, ONLY : &        ! Domain parameters
17      & jpi, &
18      & jpj, &
19      & jpim1
20   USE in_out_manager, ONLY : & ! I/O manager
21      & lwp,    &
22      & numout 
23   USE obs_surf_def             ! Surface observation definitions
24   USE dom_oce, ONLY : &        ! Domain variables
25      & tmask, &
26      & tmask_i, &
27      & e1t,   &
28      & e2t,   &
29      & gphit
30   USE obs_inter_h2d
31   USE obs_utils               ! Various observation tools
32   USE obs_inter_sup
33
34   IMPLICIT NONE
35   PRIVATE
36
37   PUBLIC   obs_rea_altbias   ! Read the altimeter bias
38
39   !!----------------------------------------------------------------------
40   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
41   !! $Id$
42   !! Software governed by the CeCILL licence (./LICENSE)
43   !!----------------------------------------------------------------------
44
45CONTAINS
46
47   SUBROUTINE obs_rea_altbias( sladata, k2dint, bias_file )
48      !!---------------------------------------------------------------------
49      !!
50      !!                   *** ROUTINE obs_rea_altbias ***
51      !!
52      !! ** Purpose : Read from file the bias data
53      !!
54      !! ** Method  :
55      !!
56      !! ** Action  :
57      !!
58      !! References :
59      !!
60      !! History : 
61      !!      ! :  2008-02 (D. Lea) Initial version
62      !!----------------------------------------------------------------------
63      !! * Modules used
64      USE iom
65      !
66      !! * Arguments
67      TYPE(obs_surf), INTENT(INOUT) :: &
68         & sladata       ! SLA data
69      INTEGER, INTENT(IN) :: k2dint
70      CHARACTER(LEN=128) :: bias_file
71
72      !! * Local declarations
73
74      CHARACTER(LEN=12), PARAMETER :: cpname = 'obs_rea_altbias'
75
76      INTEGER :: jobs         ! Obs loop variable
77      INTEGER :: jpialtbias   ! Number of grid point in latitude for the bias
78      INTEGER :: jpjaltbias   ! Number of grid point in longitude for the bias
79      INTEGER :: iico         ! Grid point indicies
80      INTEGER :: ijco
81      INTEGER :: i_nx_id      ! Index to read the NetCDF file
82      INTEGER :: i_ny_id      !
83      INTEGER :: i_file_id    !
84      INTEGER :: i_var_id
85
86      REAL(wp), DIMENSION(1) :: &
87         & zext, &
88         & zobsmask
89      REAL(wp), DIMENSION(2,2,1) :: &
90         & zweig
91      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: &
92         & zmask, &
93         & zbias, &
94         & zglam, &
95         & zgphi
96      REAL(wp), DIMENSION(jpi,jpj) ::   z_altbias
97      REAL(wp) :: zlam
98      REAL(wp) :: zphi
99      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: &
100         & igrdi, &
101         & igrdj
102      INTEGER :: numaltbias
103
104      IF(lwp)WRITE(numout,*) 
105      IF(lwp)WRITE(numout,*) ' obs_rea_altbias : '
106      IF(lwp)WRITE(numout,*) ' ------------- '
107      IF(lwp)WRITE(numout,*) '   Read altimeter bias'
108
109      ! Open the file
110
111      z_altbias(:,:)=0.0_wp
112      numaltbias=0
113
114      IF(lwp)WRITE(numout,*) 'Opening ',bias_file
115
116      CALL iom_open( bias_file, numaltbias, ldstop=.FALSE. )
117     
118
119      IF (numaltbias .GT. 0) THEN     
120
121         ! Get the Alt bias data
122         
123         CALL iom_get( numaltbias, jpdom_data, 'altbias', z_altbias(:,:), 1 )
124         
125         ! Close the file
126         
127         CALL iom_close(numaltbias)     
128         
129      ELSE
130
131         IF(lwp)WRITE(numout,*) 'no file found'
132     
133      ENDIF
134
135      ! Intepolate the bias already on the model grid at the observation point
136 
137      ALLOCATE( &
138         & igrdi(2,2,sladata%nsurf), &
139         & igrdj(2,2,sladata%nsurf), &
140         & zglam(2,2,sladata%nsurf), &
141         & zgphi(2,2,sladata%nsurf), &
142         & zmask(2,2,sladata%nsurf), &
143         & zbias(2,2,sladata%nsurf)  &
144         & )
145         
146      DO jobs = 1, sladata%nsurf
147
148         igrdi(1,1,jobs) = sladata%mi(jobs)-1
149         igrdj(1,1,jobs) = sladata%mj(jobs)-1
150         igrdi(1,2,jobs) = sladata%mi(jobs)-1
151         igrdj(1,2,jobs) = sladata%mj(jobs)
152         igrdi(2,1,jobs) = sladata%mi(jobs)
153         igrdj(2,1,jobs) = sladata%mj(jobs)-1
154         igrdi(2,2,jobs) = sladata%mi(jobs)
155         igrdj(2,2,jobs) = sladata%mj(jobs)
156
157      END DO
158
159      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, &
160         &                  igrdi, igrdj, glamt, zglam )
161      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, &
162         &                  igrdi, igrdj, gphit, zgphi )
163      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, &
164         &                  igrdi, igrdj, tmask(:,:,1), zmask )
165      CALL obs_int_comm_2d( 2, 2, sladata%nsurf, jpi, jpj, &
166         &                  igrdi, igrdj, z_altbias, zbias )
167
168      DO jobs = 1, sladata%nsurf
169
170         zlam = sladata%rlam(jobs)
171         zphi = sladata%rphi(jobs)
172         iico = sladata%mi(jobs)
173         ijco = sladata%mj(jobs)
174           
175         CALL obs_int_h2d_init( 1, 1, k2dint, zlam, zphi,         &
176            &                   zglam(:,:,jobs), zgphi(:,:,jobs), &
177            &                   zmask(:,:,jobs), zweig, zobsmask )
178           
179         CALL obs_int_h2d( 1, 1,      &
180            &              zweig, zbias(:,:,jobs),  zext )
181
182         ! adjust mdt with bias field
183         sladata%rext(jobs,2) = sladata%rext(jobs,2) - zext(1)
184           
185      END DO
186
187      DEALLOCATE( &
188         & igrdi, &
189         & igrdj, &
190         & zglam, &
191         & zgphi, &
192         & zmask, &
193         & zbias  &
194         & )
195         
196   END SUBROUTINE obs_rea_altbias
197
198
199 
200END MODULE obs_read_altbias
Note: See TracBrowser for help on using the repository browser.