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/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/OBS – NEMO

source: NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/OBS/obs_read_altbias.F90 @ 14219

Last change on this file since 14219 was 14219, checked in by mcastril, 4 years ago

Add Mixed Precision support by Oriol Tintó

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