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 trunk/NEMOGCM/NEMO/OPA_SRC/OBS – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_altbias.F90 @ 2715

Last change on this file since 2715 was 2715, checked in by rblod, 13 years ago

First attempt to put dynamic allocation on the trunk

  • Property svn:keywords set to Id
File size: 6.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 oce, ONLY : &           ! Model variables
31      & sshn
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   !!----------------------------------------------------------------------
44   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
45   !! $Id$
46   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48
49CONTAINS
50
51   SUBROUTINE obs_rea_altbias( kslano, sladata, k2dint, bias_file )
52      !!---------------------------------------------------------------------
53      !!
54      !!                   *** ROUTINE obs_rea_altbias ***
55      !!
56      !! ** Purpose : Read from file the bias data
57      !!
58      !! ** Method  :
59      !!
60      !! ** Action  :
61      !!
62      !! References :
63      !!
64      !! History : 
65      !!      ! :  2008-02 (D. Lea) Initial version
66      !!----------------------------------------------------------------------
67      !! * Modules used
68      USE iom
69      USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released
70      USE wrk_nemo, ONLY: z_altbias => wrk_2d_1   ! Array to store the alt bias values
71      !
72      !! * Arguments
73      INTEGER, INTENT(IN) :: kslano      ! Number of SLA Products
74      TYPE(obs_surf), DIMENSION(kslano), INTENT(INOUT) :: &
75         & sladata       ! SLA data
76      INTEGER, INTENT(IN) :: k2dint
77      CHARACTER(LEN=128) :: bias_file
78
79      !! * Local declarations
80
81      CHARACTER(LEN=12), PARAMETER :: cpname = 'obs_rea_altbias'
82
83      INTEGER :: jslano       ! Data set loop variable
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) :: zlam
105      REAL(wp) :: zphi
106      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: &
107         & igrdi, &
108         & igrdj
109      INTEGER :: numaltbias
110
111      IF(wrk_in_use(2, 1))THEN
112         CALL ctl_stop('obs_rea_altbias : requested workspace array unavailable.')
113         RETURN
114      END IF
115
116      IF(lwp)WRITE(numout,*) 
117      IF(lwp)WRITE(numout,*) ' obs_rea_altbias : '
118      IF(lwp)WRITE(numout,*) ' ------------- '
119      IF(lwp)WRITE(numout,*) '   Read altimeter bias'
120
121      ! Open the file
122
123      z_altbias(:,:)=0.0_wp
124      numaltbias=0
125
126      IF(lwp)WRITE(numout,*) 'Opening ',bias_file
127
128      CALL iom_open( bias_file, numaltbias, ldstop=.FALSE. )
129     
130
131      IF (numaltbias .GT. 0) THEN     
132
133         ! Get the Alt bias data
134         
135         CALL iom_get( numaltbias, jpdom_data, 'altbias', z_altbias(:,:), 1 )
136         
137         ! Close the file
138         
139         CALL iom_close(numaltbias)     
140         
141      ELSE
142
143         IF(lwp)WRITE(numout,*) 'no file found'
144     
145      ENDIF
146
147      ! Intepolate the bias already on the model grid at the observation point
148 
149      DO jslano = 1, kslano
150
151         ALLOCATE( &
152            & igrdi(2,2,sladata(jslano)%nsurf), &
153            & igrdj(2,2,sladata(jslano)%nsurf), &
154            & zglam(2,2,sladata(jslano)%nsurf), &
155            & zgphi(2,2,sladata(jslano)%nsurf), &
156            & zmask(2,2,sladata(jslano)%nsurf), &
157            & zbias(2,2,sladata(jslano)%nsurf)  &
158            & )
159         
160         DO jobs = 1, sladata(jslano)%nsurf
161
162            igrdi(1,1,jobs) = sladata(jslano)%mi(jobs)-1
163            igrdj(1,1,jobs) = sladata(jslano)%mj(jobs)-1
164            igrdi(1,2,jobs) = sladata(jslano)%mi(jobs)-1
165            igrdj(1,2,jobs) = sladata(jslano)%mj(jobs)
166            igrdi(2,1,jobs) = sladata(jslano)%mi(jobs)
167            igrdj(2,1,jobs) = sladata(jslano)%mj(jobs)-1
168            igrdi(2,2,jobs) = sladata(jslano)%mi(jobs)
169            igrdj(2,2,jobs) = sladata(jslano)%mj(jobs)
170
171         END DO
172
173         CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
174            &                  igrdi, igrdj, glamt, zglam )
175         CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
176            &                  igrdi, igrdj, gphit, zgphi )
177         CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
178            &                  igrdi, igrdj, tmask(:,:,1), zmask )
179         CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
180            &                  igrdi, igrdj, z_altbias, zbias )
181
182         DO jobs = 1, sladata(jslano)%nsurf
183
184            zlam = sladata(jslano)%rlam(jobs)
185            zphi = sladata(jslano)%rphi(jobs)
186            iico = sladata(jslano)%mi(jobs)
187            ijco = sladata(jslano)%mj(jobs)
188           
189            CALL obs_int_h2d_init( 1, 1, k2dint, zlam, zphi,         &
190               &                   zglam(:,:,jobs), zgphi(:,:,jobs), &
191               &                   zmask(:,:,jobs), zweig, zobsmask )
192           
193            CALL obs_int_h2d( 1, 1,      &
194               &              zweig, zbias(:,:,jobs),  zext )
195
196            ! adjust mdt with bias field
197            sladata(jslano)%rext(jobs,2) = &
198               sladata(jslano)%rext(jobs,2) - zext(1)
199           
200         END DO
201
202         DEALLOCATE( &
203            & igrdi, &
204            & igrdj, &
205            & zglam, &
206            & zgphi, &
207            & zmask, &
208            & zbias  &
209            & )
210         
211      END DO
212
213      IF(wrk_not_released(2, 1))THEN
214         CALL ctl_stop('obs_rea_altbias : failed to release workspace array.')
215      END IF
216
217   END SUBROUTINE obs_rea_altbias
218
219
220 
221END MODULE obs_read_altbias
Note: See TracBrowser for help on using the repository browser.