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_bias.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_bias.F90 @ 15180

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

Further generification, particularly surrounding additional and extra variables.

File size: 8.9 KB
Line 
1MODULE obs_bias
2   !!======================================================================
3   !!                       ***  MODULE obs_bias  ***
4   !! Observation diagnostics: Read the bias for observation data
5   !!======================================================================
6   !!----------------------------------------------------------------------
7   !!   obs_app_bias : Driver for reading and applying the bias
8   !!----------------------------------------------------------------------
9   !! * Modules used   
10   USE par_kind, ONLY : &       ! Precision variables
11      & wp
12   USE par_oce, ONLY : &        ! Domain parameters
13      & jpi, &
14      & jpj
15   USE in_out_manager, ONLY : & ! I/O manager
16      & lwp,    &
17      & numout 
18   USE obs_surf_def             ! Surface observation definitions
19   USE dom_oce, ONLY : &        ! Domain variables
20      & tmask, &
21      & gphit, &
22      & glamt
23   USE obs_inter_h2d
24   USE obs_utils               ! Various observation tools
25   USE obs_inter_sup
26   IMPLICIT NONE
27   !! * Routine accessibility
28   PRIVATE
29   PUBLIC obs_app_bias     ! Read the observation bias
30CONTAINS
31   SUBROUTINE obs_app_bias( obsdata, kvar, k2dint, knumtypes, &
32                            cl_bias_files, cd_biasname )
33      !!---------------------------------------------------------------------
34      !!
35      !!                   *** ROUTINE obs_app_bias ***
36      !!
37      !! ** Purpose : Read bias data from files and apply correction to
38      !!              observations
39      !!
40      !! ** Method  :
41      !!
42      !! ** Action  :
43      !!
44      !! References :
45      !!
46      !! History :
47      !!      ! :  2014-08 (J. While) Bias correction code for SST obs,
48      !!      !                       based on obs_rea_altbias
49      !!      ! :  2021-07 (D. Ford)  Renamed obs_app_bias and made generic
50      !!----------------------------------------------------------------------
51      !! * Modules used
52      USE iom
53      USE netcdf
54      !! * Arguments
55
56      TYPE(obs_surf), INTENT(INOUT) :: obsdata       ! Observation data
57      INTEGER, INTENT(IN) :: kvar    ! Index of obs type being bias corrected
58      INTEGER, INTENT(IN) :: k2dint
59      INTEGER, INTENT(IN) :: knumtypes !number of bias types to read in
60      CHARACTER(LEN=128), DIMENSION(knumtypes), INTENT(IN) :: &
61                          cl_bias_files !List of files to read
62      CHARACTER(LEN=128), INTENT(IN) :: cd_biasname  !Variable name in file
63      !! * Local declarations
64      INTEGER :: jobs         ! Obs loop variable
65      INTEGER :: iico         ! Grid point indices
66      INTEGER :: ijco
67      INTEGER :: jt
68      INTEGER, DIMENSION(knumtypes) :: &
69         & ibiastypes             ! Array of the bias types in each file
70      REAL(wp), DIMENSION(jpi,jpj,knumtypes) :: & 
71         & z_obsbias              ! Array to store the bias values
72      REAL(wp), DIMENSION(jpi,jpj) :: & 
73         & z_obsbias_2d           ! Array to store the bias values   
74      REAL(wp), DIMENSION(1) :: &
75         & zext, &
76         & zobsmask
77      REAL(wp), DIMENSION(2,2,1) :: &
78         & zweig
79      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: &
80         & zmask, &
81         & zglam, &
82         & zgphi
83      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: &
84         & zmask_tmp, &
85         & zglam_tmp, &
86         & zgphi_tmp   
87      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::  zbias   
88      REAL(wp) :: zlam
89      REAL(wp) :: zphi
90      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: &
91         & igrdi, &
92         & igrdj
93      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: &
94         & igrdi_tmp, &
95         & igrdj_tmp   
96      INTEGER :: numobsbias
97      INTEGER(KIND=NF90_INT) :: ifile_source
98     
99      INTEGER :: incfile
100      INTEGER :: jtype
101      INTEGER :: iret 
102      INTEGER :: inumtype
103      IF(lwp)WRITE(numout,*) 
104      IF(lwp)WRITE(numout,*) 'obs_app_bias : '
105      IF(lwp)WRITE(numout,*) '----------------- '
106      IF(lwp)WRITE(numout,*) 'Read observation bias for ', TRIM(obsdata%cvars(kvar))
107      ! Open and read the files
108      z_obsbias(:,:,:)=0.0_wp
109      DO jtype = 1, knumtypes
110     
111         numobsbias=0
112         IF(lwp)WRITE(numout,*) 'Opening ',cl_bias_files(jtype)
113         CALL iom_open( cl_bias_files(jtype), numobsbias, ldstop=.FALSE. )       
114         IF (numobsbias > 0) THEN
115     
116            !Read the bias type from the file
117            !No IOM get attribute command at time of writing,
118            !so have to use NETCDF
119            !routines directly - should be upgraded in the future
120            iret=NF90_OPEN(TRIM(cl_bias_files(jtype)), NF90_NOWRITE, incfile)
121            iret=NF90_GET_ATT( incfile, NF90_GLOBAL, TRIM(obsdata%cvars(kvar))//"_source", &
122                              ifile_source )
123            ibiastypes(jtype) = ifile_source                 
124            iret=NF90_CLOSE(incfile)       
125           
126            IF ( iret /= 0  ) CALL ctl_stop( &
127               'obs_app_bias : Cannot read bias type from file '// &
128               cl_bias_files(jtype) )
129            ! Get the bias data
130            CALL iom_get( numobsbias, jpdom_data, TRIM(cd_biasname), z_obsbias_2d(:,:), 1 )
131            z_obsbias(:,:,jtype) = z_obsbias_2d(:,:)       
132            ! Close the file
133            CALL iom_close(numobsbias)       
134         ELSE
135            CALL ctl_stop('obs_app_bias: File '// & 
136                           TRIM( cl_bias_files(jtype) )//' Not found')
137         ENDIF
138      END DO
139           
140      ! Interpolate the bias already on the model grid at the observation point
141      ALLOCATE( &
142         & igrdi(2,2,obsdata%nsurf), &
143         & igrdj(2,2,obsdata%nsurf), &
144         & zglam(2,2,obsdata%nsurf), &
145         & zgphi(2,2,obsdata%nsurf), &
146         & zmask(2,2,obsdata%nsurf)  )
147       
148      DO jobs = 1, obsdata%nsurf 
149         igrdi(1,1,jobs) = obsdata%mi(jobs)-1
150         igrdj(1,1,jobs) = obsdata%mj(jobs)-1
151         igrdi(1,2,jobs) = obsdata%mi(jobs)-1
152         igrdj(1,2,jobs) = obsdata%mj(jobs)
153         igrdi(2,1,jobs) = obsdata%mi(jobs)
154         igrdj(2,1,jobs) = obsdata%mj(jobs)-1
155         igrdi(2,2,jobs) = obsdata%mi(jobs)
156         igrdj(2,2,jobs) = obsdata%mj(jobs)
157      END DO
158      CALL obs_int_comm_2d( 2, 2, obsdata%nsurf, jpi, jpj, &
159         &                  igrdi, igrdj, glamt, zglam )
160      CALL obs_int_comm_2d( 2, 2, obsdata%nsurf, jpi, jpj, &
161         &                  igrdi, igrdj, gphit, zgphi )
162      CALL obs_int_comm_2d( 2, 2, obsdata%nsurf, jpi, jpj, &
163         &                  igrdi, igrdj, tmask(:,:,1), zmask )
164      DO jtype = 1, knumtypes
165         
166         !Find the number observations of type and allocate tempory arrays
167         inumtype = COUNT( obsdata%ntyp(:) == ibiastypes(jtype) )
168         ALLOCATE( &
169            & igrdi_tmp(2,2,inumtype), &
170            & igrdj_tmp(2,2,inumtype), &
171            & zglam_tmp(2,2,inumtype), &
172            & zgphi_tmp(2,2,inumtype), &
173            & zmask_tmp(2,2,inumtype), &
174            & zbias( 2,2,inumtype ) )
175         jt=1
176         DO jobs = 1, obsdata%nsurf 
177            IF ( obsdata%ntyp(jobs) == ibiastypes(jtype) ) THEN
178               igrdi_tmp(:,:,jt) = igrdi(:,:,jobs) 
179               igrdj_tmp(:,:,jt) = igrdj(:,:,jobs)
180               zglam_tmp(:,:,jt) = zglam(:,:,jobs)
181               zgphi_tmp(:,:,jt) = zgphi(:,:,jobs)
182               zmask_tmp(:,:,jt) = zmask(:,:,jobs)
183               jt = jt +1
184            ENDIF
185         END DO
186                         
187         CALL obs_int_comm_2d( 2, 2, inumtype, jpi, jpj, &
188               &           igrdi_tmp(:,:,:), igrdj_tmp(:,:,:), &
189               &           z_obsbias(:,:,jtype), zbias(:,:,:) )
190         jt=1
191         DO jobs = 1, obsdata%nsurf
192            IF ( obsdata%ntyp(jobs) == ibiastypes(jtype) ) THEN
193               zlam = obsdata%rlam(jobs)
194               zphi = obsdata%rphi(jobs)
195               iico = obsdata%mi(jobs)
196               ijco = obsdata%mj(jobs)         
197               CALL obs_int_h2d_init( 1, 1, k2dint, zlam, zphi,         &
198                  &                   zglam_tmp(:,:,jt), &
199                  &                   zgphi_tmp(:,:,jt), &
200                  &                   zmask_tmp(:,:,jt), zweig, zobsmask )
201               CALL obs_int_h2d( 1, 1, zweig, zbias(:,:,jt),  zext )
202               ! adjust observations with bias field
203               obsdata%robs(jobs,kvar) = obsdata%robs(jobs,kvar) - zext(1)
204               jt=jt+1
205            ENDIF
206         END DO 
207               
208         !Deallocate arrays
209         DEALLOCATE( &
210         & igrdi_tmp, &
211         & igrdj_tmp, &
212         & zglam_tmp, &
213         & zgphi_tmp, &
214         & zmask_tmp, &
215         & zbias )           
216      END DO
217      DEALLOCATE( &
218         & igrdi, &
219         & igrdj, &
220         & zglam, &
221         & zgphi, &
222         & zmask )
223
224      IF(lwp) THEN
225         WRITE(numout,*) " "
226         WRITE(numout,*) "Bias correction applied successfully"
227         WRITE(numout,*) "Obs types: ",ibiastypes(:), &
228                              " Have all been bias corrected\n"
229      ENDIF
230   END SUBROUTINE obs_app_bias
231 
232END MODULE obs_bias
Note: See TracBrowser for help on using the repository browser.