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.
obssla_io.h90 on Ticket #2269 – Attachment – NEMO

Ticket #2269: obssla_io.h90

File obssla_io.h90, 9.1 KB (added by cbricaud, 5 years ago)
Line 
1   !!----------------------------------------------------------------------
2   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
3   !! $Id: obssla_io.h90 2287 2010-10-18 07:53:52Z smasson $
4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
5   !!----------------------------------------------------------------------
6
7   SUBROUTINE read_avisofile( cdfilename, inpfile, kunit, ldwp, ldgrid )
8      !!---------------------------------------------------------------------
9      !!
10      !!                     ** ROUTINE read_avisofile **
11      !!
12      !! ** Purpose : Read from file the AVISO SLA observations.
13      !!
14      !! ** Method  : The data file is a NetCDF file.
15      !!
16      !! ** Action  :
17      !!
18      !! References : http://www.aviso.oceanobs.com
19      !!
20      !! History :
21      !!          ! 09-01 (K. Mogensen) Original based on old versions
22      !!----------------------------------------------------------------------
23      !! * Arguments
24      CHARACTER(LEN=*) :: cdfilename ! Input filename
25      TYPE(obfbdata)   :: inpfile    ! Output obfbdata structure
26      INTEGER          :: kunit      ! Unit for output
27      LOGICAL          :: ldwp       ! Print info
28      LOGICAL          :: ldgrid     ! Save grid info in data structure
29      !! * Local declarations
30      CHARACTER(LEN=14),PARAMETER :: cpname = 'read_avisofile'
31      INTEGER :: i_file_id     ! netcdf IDS
32      INTEGER :: i_tracks_id
33      INTEGER :: i_cycles_id
34      INTEGER :: i_data_id
35      INTEGER :: i_var_id
36      INTEGER :: i_time_id
37      INTEGER, PARAMETER :: imaxdim = 2    ! Assumed maximum for no. dims. in file
38      INTEGER, DIMENSION(2) :: idims       ! Dimensions in file
39      INTEGER :: iilen         ! Length of netCDF attributes
40      INTEGER :: itype         ! Typeof netCDF attributes
41      REAL(fbdp) :: zsca       ! Scale factor
42      REAL(fbdp) :: zfill      ! Fill value
43      CHARACTER(len=3) ::  cmission      ! Mission global attribute
44      INTEGER :: itracks       ! Maximum number of passes in file
45      INTEGER :: icycles       ! Maximum number of cycles for each pass
46      INTEGER :: idata         ! Number of data per parameter in current file
47      INTEGER :: itime         ! Number of data per parameter in current file
48      REAL(fbdp) :: zdeltat    ! Time gap getween two measurements in seconds
49      INTEGER, DIMENSION(:), POINTER :: &
50         & iptracks,     &  ! List of passes contained in current file
51         & ipnbpoints,   &  ! Number of points per pass
52         & ipdataindexes    ! Index of data in theoretical profile
53      INTEGER, DIMENSION(:,:), POINTER :: &
54         & ipcycles         ! List of cycles per pass
55      REAL(fbdp), DIMENSION(:), POINTER :: &
56         & zphi,   &        ! Latitudes
57         & zlam             ! Longitudes
58      REAL(fbdp), DIMENSION(:,:), POINTER :: &
59         & zbegindates      ! Date of point with index 0
60      REAL(fbdp) :: zbeginmiss    ! Missing data for dates
61      REAL(fbsp), DIMENSION(:), POINTER :: &
62         & zsla             ! SLA data
63      REAL(fbdp), DIMENSION(:), POINTER :: &
64         & zjuld            ! Julian date
65      LOGICAL, DIMENSION(:), POINTER :: &
66         & llskip           ! Skip observation
67      CHARACTER(len=14) :: cdjuldref    ! Julian data reference
68      INTEGER :: imission   ! Mission number converted from Mission global
69                            ! netCDF atttribute.
70      CHARACTER(len=255) :: ctmp
71      INTEGER :: iobs
72      INTEGER :: jl
73      INTEGER :: jm
74      INTEGER :: jj
75      INTEGER :: ji
76      INTEGER :: jk
77      INTEGER :: jobs
78      INTEGER :: jcycle
79
80      ! Open the file
81
82      CALL chkerr( nf90_open( TRIM( cdfilename ), nf90_nowrite, i_file_id ), &
83         &         cpname, __LINE__ )
84
85      ! Get the netCDF dimensions
86     
87      CALL chkerr( nf90_inq_dimid( i_file_id, 'time', i_time_id ),  &
88         &         cpname, __LINE__ )
89      CALL chkerr( nf90_inquire_dimension( i_file_id, i_time_id, &
90         &                                 len = itime ),  &
91         &         cpname, __LINE__ )
92
93      ! Allocate memory for input data
94
95      ALLOCATE( &
96         & zphi         ( itime    ), &   
97         & zlam         ( itime    ), & 
98         & zsla         ( itime    ), &
99         & zjuld        ( itime    ), &
100         & llskip       ( itime    )  &
101         & )
102
103      ! Get time
104
105      CALL chkerr( nf90_inq_varid( i_file_id, 'time', i_var_id ), &
106         &         cpname, __LINE__ )
107      idims(1) = itime
108      CALL chkdim( i_file_id, i_var_id, 1, idims, cpname, __LINE__ )
109      CALL chkerr( nf90_get_var  ( i_file_id, i_var_id, zjuld),   &
110         &         cpname, __LINE__ )
111      zsca = 1.0
112      zjuld(:) = zsca * zjuld(:)
113
114
115      ! Get longitudes
116
117      CALL chkerr( nf90_inq_varid( i_file_id, 'longitude', i_var_id ), &
118         &         cpname, __LINE__ )
119      idims(1) = itime
120      CALL chkdim( i_file_id, i_var_id, 1, idims, cpname, __LINE__ )
121      CALL chkerr( nf90_get_var  ( i_file_id, i_var_id, zlam),   &
122         &         cpname, __LINE__ )
123      zsca = 1.0
124      IF (nf90_inquire_attribute( i_file_id, i_var_id, 'scale_factor') &
125         &                         == nf90_noerr) THEN
126         CALL chkerr( nf90_get_att( i_file_id, i_var_id, &
127            &                     'scale_factor',zsca), cpname,  __LINE__)
128      ENDIF
129      zlam(:) = zsca * zlam(:)
130     
131      WHERE(zlam .GT. 180.0)zlam=zlam-360.
132 
133      ! Get latitudes
134     
135      CALL chkerr( nf90_inq_varid( i_file_id, 'latitude', i_var_id ), &
136         &         cpname, __LINE__ )
137      idims(1) = itime
138      CALL chkdim( i_file_id, i_var_id, 1, idims, cpname, __LINE__ )
139      CALL chkerr( nf90_get_var  ( i_file_id, i_var_id, zphi),   &
140         &         cpname, __LINE__ )
141      zsca = 1.0
142      IF (nf90_inquire_attribute( i_file_id, i_var_id, 'scale_factor') &
143         &                       == nf90_noerr) THEN
144         CALL chkerr( nf90_get_att( i_file_id, i_var_id, &
145            &                     'scale_factor',zsca), cpname,  __LINE__)
146      ENDIF
147      zphi(:) = zsca * zphi(:)
148     
149      cdjuldref='23014.0121781'
150     
151      CALL chkerr( nf90_inq_varid( i_file_id, 'sla_filtered', i_var_id ), &
152         &         cpname, __LINE__ )
153      idims(1) = itime
154      CALL chkdim( i_file_id, i_var_id, 1, idims, cpname, __LINE__ )
155      CALL chkerr( nf90_get_var  ( i_file_id, i_var_id, zsla),   &
156         &         cpname, __LINE__ )
157      zsca = 1.0
158      IF (nf90_inquire_attribute( i_file_id, i_var_id, 'scale_factor') &
159         &                        == nf90_noerr) THEN
160         CALL chkerr( nf90_get_att( i_file_id, i_var_id, &
161            &                       'scale_factor',zsca), cpname, __LINE__ )
162      ENDIF
163      zfill = 0.0
164      IF (nf90_inquire_attribute( i_file_id, i_var_id, '_FillValue') &
165         &                      == nf90_noerr) THEN
166         CALL chkerr( nf90_get_att( i_file_id, i_var_id, &
167            &                     '_FillValue',zfill), cpname,  __LINE__ )
168      ENDIF
169      WHERE(zsla(:) /=  zfill)
170         zsla(:) = zsca * zsla(:)
171      ELSEWHERE
172         zsla(:) = fbrmdi
173      END WHERE
174     
175      ! Close the file
176      CALL chkerr( nf90_close( i_file_id ), cpname, __LINE__ )
177
178      ! Compute Julian dates for all observations
179
180      ! Get rid of missing data
181      llskip(:) = .FALSE.
182      jm = 0
183      !DO jobs = 1, idata
184      DO jobs = 1, itime
185         !DO jcycle = 1, icycles
186            jm = jm + 1
187            IF (zsla(jobs) == fbrmdi) llskip(jm) = .TRUE.
188         !END DO
189      END DO
190     
191      ! Allocate obfbdata
192
193      iobs = COUNT( .NOT.llskip(:) )
194      CALL init_obfbdata( inpfile )
195      CALL alloc_obfbdata( inpfile, 1, iobs, 1, 0, 0, ldgrid )
196      inpfile%cname(1) = 'SLA'
197
198      ! Fill the obfbdata structure from input data
199
200      inpfile%cdjuldref = "19500101000000"
201      iobs = 0
202      jm = 0
203      DO jobs = 1, itime
204            jm = jm + 1
205            IF (llskip(jm)) CYCLE
206            iobs = iobs + 1
207            ! Characters
208            WRITE(inpfile%cdwmo(iobs),'(A3,A5)') cmissions(imission), '     '
209            WRITE(inpfile%cdtyp(iobs),'(I4)') imission
210            ! Real values
211            inpfile%plam(iobs)         = zlam(jobs)
212            inpfile%pphi(iobs)         = zphi(jobs)
213            inpfile%pob(1,iobs,1)      = zsla(jobs)
214            inpfile%ptim(iobs)         = zjuld(jobs)
215            inpfile%pdep(1,iobs)       = 0.0
216            ! Integers
217            inpfile%kindex(iobs)       = iobs
218            inpfile%ioqc(iobs)      = 1
219            inpfile%ivqc(iobs,1)    = 1
220            inpfile%ivlqc(1,iobs,1) = 1
221            inpfile%ipqc(iobs)         = 0
222            inpfile%ipqcf(:,iobs)      = 0
223            inpfile%itqc(iobs)         = 0
224            inpfile%itqcf(:,iobs)      = 0
225            inpfile%ivqcf(:,iobs,1)    = 0
226            inpfile%ioqcf(:,iobs)      = 0
227            inpfile%idqc(1,iobs)       = 0
228            inpfile%idqcf(1,1,iobs)    = 0
229            inpfile%ivlqcf(:,1,iobs,1) = 0
230      END DO
231
232
233      ! Deallocate memory for input data
234
235      DEALLOCATE( &
236         & zphi,          &
237         & zlam,          & 
238         & zsla,          &
239         & zjuld,         &
240         & llskip         &
241         & )
242
243   END SUBROUTINE read_avisofile
244