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.
bias.F90 in branches/UKMO/dev_r5518_pcbias_ipc/NEMOGCM/NEMO/OPA_SRC/ASM – NEMO

source: branches/UKMO/dev_r5518_pcbias_ipc/NEMOGCM/NEMO/OPA_SRC/ASM/bias.F90 @ 7652

Last change on this file since 7652 was 7652, checked in by isabella, 7 years ago

adding output messages to understand what model does

File size: 49.5 KB
Line 
1MODULE bias 
2   !! Is used by OPA and STEP
3   !!======================================================================
4   !!                 *** Module bias ***
5   !! Code to estimate and apply bias correction.
6   !! The bias is in T/S and Pressure. It follows the generalized
7   !! bias algorithm presented in Balmaseda et al 2007.
8   !!
9   !! It can be read from a file offline, estimated online from relaxation
10   !! terms or from assimilation increments (this latter estimtd in inner loop)
11   !!
12   !! The parameters for the time evolution of the bias can be different
13   !! from the relaxation terms and for the assim increments. Only the
14   !! parameter for the relaxtion terms are considered here.
15   !!
16   !! The offline bias term can contain the seasonal cycle.
17   !!
18   !! The time evolution of the bias for relaxtion is estimated as followed
19   !!   bias_rlx(t+1)=t_rlx_mem*bias_rlx(t)+t_rlx_upd*(t/s)trdmp.
20   !!
21   !! The total bias in T/S is partion between the correction to T/S only
22   !!  (fb_t) and the correction applied to the pressure gradient (fb_p).
23   !!  We impose that (fb_p=1.-fb_t). These factors can be different for the
24   !!  different terms(fb_t_rxl,fb_t_asm,fb_t_ofl)
25   !!
26   !!    (t/s)bias =  fb_t_ofl * (t/s)bias_ofl +
27   !!                 fb_t_rlx * (t/s)bias_rlx +
28   !!                 fb_t_asm * (t/s)bias_asm
29   !!    (t/s)bias_p =fb_p_ofl * (t/s)bias_ofl+
30   !!                 fb_p_rlx * (t/s)bias_rlx_p +
31   !!                 fb_p_asm * (t/s)bias_asm_p
32   !!    (t/s)bias is applied directely to correct T and S
33   !!    (t/s)bias_p is used to compute rhd_pc and gru/v_pc
34   !!
35   !!  Note: the above is an adhoc /simple way of making the partition
36   !!        between bias in pressure and bias in T/S. It would be better
37   !!        if the partition is done at the time of estimating the time
38   !!        evolution of the bias. That would mean doubling the number of
39   !!        3D arrays.
40   !!
41   !!  New addtion: (not in Balmaseda et al 2007):
42   !!  A more physical alternative to the partition of the bias can be
43   !!  done in terms of the inertial frequency: when the time scales of
44   !!  adjustment are shorter that >1/f (Equator), the bias correction should
45   !!  be in the the pressure term. Otherwise, it can act directly in T/S.
46   !!  NOTE that the bias correction in the pressure term here (following
47   !!  (Bell et al 2007) is just the "opposite" as the semi-prognostic method
48   !!  in Greatbatch et al 2004.
49   !!  The use of this partition is controlled by ln_inertial=.true.
50   !! 
51   !!
52   !!        2009-03              (M.A. Balmaseda ECMWF)
53   !!======================================================================
54
55   !!----------------------------------------------------------------------
56   !!   bias_init  : Read in the bias namelist and the bias arrays
57   !!   tra_bias   : Apply the bias fields on T/S directly
58   !!   dyn_bias   : Compute density correction for dynamic hpg
59   !!   bias_opn   : open bias files for restart capabilities
60   !!   bias_wrt   : write bias fies "     "          "
61   !!----------------------------------------------------------------------
62   !! * Modules used
63   USE par_kind, ONLY: &
64      & wp
65   USE par_oce, ONLY: &
66      & jpi, &
67      & jpj, &
68      & jpk
69   USE dom_oce, ONLY: &
70      & rdt,          &
71      & ln_zps,       &
72      & gphit
73   USE phycst,  ONLY: &
74      & rday,         &
75      & rad
76   USE oce, ONLY: &
77      & tsb, tsn, tsa, &
78      & rhop,          &
79      & gtsu, gtsv
80   USE dynhpg, ONLY:   &
81      & ln_dynhpg_imp     
82   USE tradmp
83   USE dtatsd, ONLY: &
84      & ln_tsd_tradmp
85   USE in_out_manager, ONLY: &
86      & lwp,          &
87      & numnam_ref,   &
88      & numnam_cfg,   &
89      & numond,       &
90      & numout,       &
91      & lrst_oce,     &
92      & nit000
93   USE iom
94   USE eosbn2
95   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
96   USE biaspar
97   USE fldread         ! read input fields
98   USE lbclnk          ! lateral boundary conditions (or mpp link)
99   USE asmpar
100   USE asminc
101   USE lib_mpp, ONLY: &
102      & ctl_stop, &
103      & ctl_nam
104
105   IMPLICIT NONE
106
107   !! * Routine accessibility
108   PRIVATE   
109   PUBLIC bias_init,   &   !: Read in the bias namelist and the bias arrays
110      &   tra_bias,    &   !: Estimate/apply bias on traces
111      &   dyn_bias,    &   !: " density correction for pressure gradient.
112      &   bias_opn,    &
113      &   bias_wrt
114
115 
116   !! * Shared variables
117   !! * Private module variables
118   REAL(wp), PRIVATE :: &
119      & bias_time_unit_asm,   &  !: bias_asm units in s ( per day = 86400 s)   
120      & bias_time_unit_rlx,   &  !: bias_rlx units in s ( 1 second)
121      & bias_time_unit_ofl,   &  !: bias_ofl units in s ( 1 second)
122      & t_rlx_mem,            &  !: time param for mem in bias_rlx model
123      & t_rlx_upd,            &  !: time param for update in bias_rlx model
124                                 !: (pct of incr for computation of bias)
125      & t_asm_mem,            &  !: time param for mem in bias_asm model
126      & t_asm_upd,            &  !: time param for update in bias_asm model
127                                 !: (pct of incr for computation of bias)
128      & fb_t_rlx,             &  !: parition of bias in T for rlx bias term
129      & fb_t_asm,             &  !: parition of bias in T for asm bias term
130      & fb_t_ofl,             &  !: parition of bias in T for ofl bias term
131      & fb_p_rlx,             &  !: parition of bias in P for rlx bias term
132      & fb_p_asm,             &  !: parition of bias in P for asm bias term
133      & fb_p_ofl,             &  !: parition of bias in P for ofl bias term
134      & fctamp,               &  !: amplification factor for T if inertial
135      & rn_maxlat_bias,       &  !: Max lat for latitudinal ramp
136      & rn_minlat_bias,       &  !: Min lat for latitudinal ramp
137      & zwgt,                 &  !: weight for IPC
138      & ztscale                  !: decay rate for IPC
139
140   LOGICAL,  PRIVATE :: lalloc
141   REAL(wp), PRIVATE, DIMENSION(:,:,:), ALLOCATABLE :: &
142      & tbias_asm, &       !: Temperature bias field
143      & sbias_asm, &       !: Salinity bias field
144      & tbias_rlx, &       !: Temperature bias field
145      & sbias_rlx, &       !: Salinity bias field
146      & tbias_asm_out, &   !: Output temperature bias field
147      & sbias_asm_out, &   !: Output salinity bias field
148      & tbias_rlx_out, &   !: Output temperature bias field
149      & sbias_rlx_out, &   !: Output salinity bias field
150      & tbias_p_out,   &   !: Output temperature bias field for P correction
151      & sbias_p_out,   &   !: Output salinity bias field for P correction
152      & tbias_i_out,   &   !: Output temperature bias field for incremental P correction
153      & sbias_i_out,   &   !: Output salinity bias field for incremental P correction
154      & tbias_asm_stscale, &   !: Short time scale temperature bias field
155      & sbias_asm_stscale, &   !: Short time scale salinity bias field
156      & tbias_asm_stscale_out, &   !: Short time scale temperature bias output field
157      & sbias_asm_stscale_out   !: Short time scale salinity bias output field
158
159   INTEGER, PRIVATE :: nn_lat_ramp     ! choice of latitude dependent ramp
160                                       ! for the pressure correction.
161                   ! 1:inertial ramp, 2:linear ramp, else:no ramp
162   LOGICAL, PRIVATE :: ln_bsyncro      ! syncronous or assincrous bias correction   
163   LOGICAL, PRIVATE :: ln_itdecay      ! evolve bias correction at every time step. 
164   LOGICAL, PRIVATE :: ln_incpc        ! incremental pressure correction plus pressure correction
165   LOGICAL, PRIVATE :: ln_incpc_only        ! incremental pressure correction only
166
167   REAL(wp), PRIVATE, DIMENSION(:,:), ALLOCATABLE :: fbcoef
168   REAL(wp), PRIVATE, DIMENSION(:,:), ALLOCATABLE :: fbcoef_stscale
169
170   INTEGER, PRIVATE ::  &
171      & numbias_asm, &    ! netcdf id of bias file from assim
172      & numbias_tot, &    ! netcdf id of bias file with total bias
173      & nn_bias_itwrt     ! time step for outputting bias pressure corr
174         
175   CHARACTER(LEN=128), PRIVATE :: &
176      & cn_bias_asm,   &  ! name of bias file from assim
177      & cn_bias_tot       ! name of bias with total/rlx bias
178
179   ! Structure of input T and S bias offline (file informations, fields read)
180   TYPE(FLD), PRIVATE, ALLOCATABLE, DIMENSION(:) ::   sf_tbias_ofl 
181   TYPE(FLD), PRIVATE, ALLOCATABLE, DIMENSION(:) ::   sf_sbias_ofl
182
183   TYPE(FLD_N), PRIVATE ::&   ! information about the fields to be read
184      &  sn_tbias_ofl, sn_sbias_ofl 
185   
186CONTAINS
187
188   SUBROUTINE bias_init
189      !!----------------------------------------------------------------------
190      !!                    ***  ROUTINE bias_init  ***
191      !!
192      !! ** Purpose : Read in the bias namelist and read in the bias fields.
193      !!
194      !! ** Method  : Read in the bias namelist and read in the bias fields.
195      !!
196      !! ** Action  :
197      !!
198      !! History :
199      !!        !  08-05  (D. Lea)    Initial version
200      !!        !  08-10  (M. Martin) Tidy
201      !!        !  09-03  (M. Balmaseda). Generalize to estimate the bias
202      !!                                  from relax and offline bias term.
203      !!                                  Introduce parameters to control the
204      !!                                  model for the bias
205      !!                                  (variables and time evolution)
206      !!----------------------------------------------------------------------
207
208      IMPLICIT NONE
209     
210      !! * Local declarations
211
212      CHARACTER(len=100) ::  cn_dir       ! dir for location ofline bias
213      INTEGER            ::  ierror
214      INTEGER            ::  ios          ! Local integer output status for namelist read
215      REAL(wp)           ::  eft_rlx,  &  ! efolding time (bias memory) in days
216         &                   eft_asm,  &  !     "      "
217         &                   log2,     &
218         &                   lenscl_bias, &  !lengthscale of the pressure bias decay between minlat and maxlat.
219         &                   minlat_bias, &     !used in ipc
220         &                   maxlat_bias    !used in ipc
221     
222      NAMELIST/nambias/ ln_bias, ln_bias_asm, ln_bias_rlx, ln_bias_ofl,   &
223         & ln_bias_ts_app, ln_bias_pc_app,                                &
224         & fb_t_asm, fb_t_rlx, fb_t_ofl, fb_p_asm, fb_p_rlx, fb_p_ofl,    &
225         & eft_rlx, t_rlx_upd, eft_asm, t_asm_upd, nn_lat_ramp,           &
226         & bias_time_unit_asm, bias_time_unit_rlx, bias_time_unit_ofl,    &
227         & cn_bias_tot, cn_bias_asm, cn_dir, sn_tbias_ofl, sn_sbias_ofl,  &
228         & ln_bsyncro, fctamp, rn_maxlat_bias, rn_minlat_bias,            &
229         & nn_bias_itwrt, ln_itdecay, ln_incpc,ln_incpc_only, ztscale, zwgt
230 
231
232      !-----------------------------------------------------------------------
233      ! Read Namelist : bias interface
234      !-----------------------------------------------------------------------
235
236
237      REWIND( numnam_ref )              ! Namelist nambias in reference namelist : Bias pressure correction
238      READ  ( numnam_ref, nambias, IOSTAT = ios, ERR = 901)
239901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambias in reference namelist', lwp )
240
241
242      ! Set additional default values (note that most values are set in the reference namelist)
243     
244      IF ( ln_asmiau ) nn_bias_itwrt = nitiaufin
245     
246      ! ... default values (NB: frequency positive => hours, negative => months)
247      !            !   file    ! frequency !  variable  ! time intep !  clim   ! 'yearly' or !
248      !            !   name    !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  !
249      sn_tbias_ofl = FLD_N( 'tbias_ofl'    ,    -1.    ,  'tbias'     ,  .TRUE.   , .FALSE. ,   'yearly', '', '', ''  )
250      sn_sbias_ofl = FLD_N( 'sbias_ofl'    ,    -1.    ,  'sbias'     ,  .TRUE.   , .FALSE. ,   'yearly', '', '', ''  )
251
252
253      REWIND( numnam_cfg )              ! Namelist nambias in configuration namelist : Bias pressure correction
254      READ  ( numnam_cfg, nambias, IOSTAT = ios, ERR = 902 )
255902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambias in configuration namelist', lwp )
256      IF(lwm) WRITE ( numond, nambias )
257
258
259      IF ( ( .NOT. ln_bias_asm ) .AND. ( .NOT. ln_bias_ofl ) .AND. ( .NOT. ln_bias_rlx ) ) THEN
260         ln_bias_ts_app = .FALSE.
261         ln_bias_pc_app = .FALSE.
262         ln_bias        = .FALSE.
263      ENDIF
264     
265      ! set up decay scales
266      log2           = LOG( 2.0_wp )
267      t_rlx_mem      = EXP( - log2 * rdt / ( eft_rlx * rday ) )
268      t_asm_mem      = EXP( - log2 * bias_time_unit_asm/ ( eft_asm * rday ) )
269     
270      ! Control print
271      IF(lwp) THEN
272         WRITE(numout,*)
273         WRITE(numout,*) 'bias_init : '
274         WRITE(numout,*) '~~~~~~~~~~~ '
275         WRITE(numout,*) '  Namelist nambias : '
276
277         WRITE(numout,*) '  Bias switches/options/variables '
278         WRITE(numout,*) '     bias main switch               ln_bias        = ',ln_bias
279         WRITE(numout,*) '     bias from assim                ln_bias_asm    = ',ln_bias_asm
280         WRITE(numout,*) '     bias from relax                ln_bias_rlx    = ',ln_bias_rlx
281         WRITE(numout,*) '     bias from offln                ln_bias_ofl    = ',ln_bias_ofl
282         WRITE(numout,*) '     bias T and S apply             ln_bias_ts_app = ',ln_bias_ts_app
283         WRITE(numout,*) '     bias pressure correctn apply   ln_bias_pc_app = ',ln_bias_pc_app
284         WRITE(numout,*) '     bias pressure correctn apply   ln_bias_pc_app = ',ln_bias_pc_app
285         WRITE(numout,*) '     lat ramp for bias correction   nn_lat_ramp    = ',nn_lat_ramp
286         WRITE(numout,*) '     time step for writing bias fld nn_bias_itwrt  = ',nn_bias_itwrt
287    WRITE(numout,*) '     evolve pcbias at each timestep ln_itdecay     = ',ln_itdecay
288    WRITE(numout,*) '     incremental press. correction  ln_incpc       = ',ln_incpc
289    WRITE(numout,*) '     incremental press. correction only  ln_incpc_only       = ',ln_incpc_only
290    WRITE(numout,*) '     incremental press. correction  zwgt           = ',zwgt
291    WRITE(numout,*) '     incremental press. correction  ztscale        = ',ztscale
292         WRITE(numout,*) '  Parameters for parition of bias term '
293         WRITE(numout,*) '                                    fb_t_rlx       = ',fb_t_rlx
294         WRITE(numout,*) '                                    fb_t_asm       = ',fb_t_asm
295         WRITE(numout,*) '                                    fb_t_ofl       = ',fb_t_ofl
296         WRITE(numout,*) '                                    fb_p_rlx       = ',fb_p_rlx
297         WRITE(numout,*) '                                    fb_p_asm       = ',fb_p_asm
298         WRITE(numout,*) '                                    fb_p_ofl       = ',fb_p_ofl
299         WRITE(numout,*) '  Parameters for time evolution of bias '
300         WRITE(numout,*) '  Rlx   efolding time (mem)         eft_rlx,t_rlx_mem = ', eft_rlx, t_rlx_mem, 1. - log2 * rdt / (eft_rlx * rday)
301         WRITE(numout,*) '        uptdate factor              t_rlx_upd         = ',t_rlx_upd
302         WRITE(numout,*) '  Asm   efolding time (mem)         eft_asm,t_asm_mem = ', eft_asm, t_asm_mem, 1. - log2 * rdt / (eft_asm * rday)
303         WRITE(numout,*) '        uptdate factor              t_asm_upd         = ',t_asm_upd
304         WRITE(numout,*) '  Filenames and input structures'
305         WRITE(numout,*) '     bias_tot filename              cn_bias_to     = ',cn_bias_tot
306         WRITE(numout,*) '     bias_asm filename              cn_bias_asm    = ',cn_bias_asm
307         WRITE(numout,*) '     bias_asm time unit (secs)  bias_time_unit_asm = ',bias_time_unit_asm
308         WRITE(numout,*) '     structure Tem bias ofl         sn_tbias_ofl   = ',sn_tbias_ofl
309         WRITE(numout,*) '     structure Sal bias ofl         sn_sbias_ofl   = ',sn_sbias_ofl
310         
311         IF ( ( (.NOT. ln_tsd_tradmp) .OR. (.NOT. ln_tradmp) ) .AND. ln_bias_rlx ) &
312            &   CALL ctl_stop (' lk_dtatem, lk_dtasal and lk_tradmp need to be true with ln_bias_rlx' )
313
314         IF ( (.NOT. ln_itdecay) .AND. ln_incpc) &   
315            &   CALL ctl_stop (' if you set ln_incpc to .true. then you need to set ln_itdecay to .true. as well' )
316
317         IF ( (.NOT. ln_incpc) .AND. ln_incpc_only) &   
318            &   CALL ctl_stop (' if you set ln_incpc_only to .true. then you need to set ln_incpc to .true. as well' )
319         
320         WRITE(numout,*) '     time step is    = ',rdt,'you choose to write pcbias at nn_bias_itwrt  = ',nn_bias_itwrt,'and end of iau is rday/rdt=',rday/rdt 
321      ENDIF
322      IF( .NOT. ln_bias ) RETURN
323
324      IF( .NOT. lalloc ) THEN
325
326         ALLOCATE( tbias(jpi,jpj,jpk)  , &
327            &      sbias(jpi,jpj,jpk)  , &
328            &      tbias_p(jpi,jpj,jpk), &
329            &      sbias_p(jpi,jpj,jpk), &
330            &      tbias_i(jpi,jpj,jpk), &
331            &      sbias_i(jpi,jpj,jpk), &
332            &      rhd_pc(jpi,jpj,jpk) , &
333            &      gru_pc(jpi,jpj)     , &
334            &      grv_pc(jpi,jpj)       )
335
336         ALLOCATE( fbcoef(jpi,jpj), fbcoef_stscale(jpi,jpj) )
337         
338         IF( ln_bias_asm ) ALLOCATE(  tbias_asm(jpi,jpj,jpk),     &
339            &                         sbias_asm(jpi,jpj,jpk),     &
340                                      tbias_asm_out(jpi,jpj,jpk), & 
341                                      sbias_asm_out(jpi,jpj,jpk), & 
342                                      tbias_p_out(jpi,jpj,jpk),   &             
343                                      sbias_p_out(jpi,jpj,jpk)    )
344
345         IF( ln_bias_rlx ) ALLOCATE(  tbias_rlx(jpi,jpj,jpk),     &
346            &                         sbias_rlx(jpi,jpj,jpk),     &
347                                      tbias_rlx_out(jpi,jpj,jpk), & 
348                                      sbias_rlx_out(jpi,jpj,jpk)  )
349
350         IF( ln_incpc )    ALLOCATE(  tbias_asm_stscale(jpi,jpj,jpk), &
351            &                         sbias_asm_stscale(jpi,jpj,jpk), &
352                                      tbias_asm_stscale_out(jpi,jpj,jpk), &
353                                      sbias_asm_stscale_out(jpi,jpj,jpk), &
354                                      tbias_i_out(jpi,jpj,jpk),   & 
355                                      sbias_i_out(jpi,jpj,jpk)   )
356
357         lalloc = .TRUE.
358
359      ENDIF
360
361      IF( ln_bias_ofl ) THEN      ! set sf_tbias_ofl and sf_sbias_ofl strctrs
362         !
363         ! tbias
364         !
365         ALLOCATE( sf_tbias_ofl(1), STAT=ierror )
366         IF( ierror > 0 ) THEN
367            CALL ctl_stop( 'bias_init: unable to allocate sf_tbias_ofl structure' )   ;    RETURN
368         ENDIF
369         ALLOCATE( sf_tbias_ofl(1)%fnow(jpi,jpj,jpk) )
370         ALLOCATE( sf_tbias_ofl(1)%fdta(jpi,jpj,jpk,2) )
371         
372         ! fill structure with values and control print
373         CALL fld_fill( sf_tbias_ofl, (/ sn_tbias_ofl /), cn_dir, 'bias_init', 'Offline T bias term ', 'nam_tbias_ofl' )
374         !
375         ! salinity bias
376         !
377         ALLOCATE( sf_sbias_ofl(1), STAT=ierror )
378         IF( ierror > 0 ) THEN
379            CALL ctl_stop( 'bias_init: unable to allocate sf_sbias_ofl structure' )   ;   RETURN
380         ENDIF
381         ALLOCATE( sf_sbias_ofl(1)%fnow(jpi,jpj,jpk) )
382         ALLOCATE( sf_sbias_ofl(1)%fdta(jpi,jpj,jpk,2) )
383         
384         ! fill structure with values and control print
385         CALL fld_fill( sf_sbias_ofl, (/ sn_sbias_ofl /), cn_dir, 'bias_init', 'Offline S bias term ', 'nam_sbias_ofl' )
386         
387      ENDIF
388
389      ! Read total bias
390      IF ( ln_bias ) THEN
391         tbias(:,:,:)   = 0.0_wp
392         sbias(:,:,:)   = 0.0_wp
393         tbias_p(:,:,:) = 0.0_wp
394         sbias_p(:,:,:) = 0.0_wp
395         tbias_i(:,:,:) = 0.0_wp
396         sbias_i(:,:,:) = 0.0_wp
397         gru_pc(:,:)    = 0.0_wp
398         grv_pc(:,:)    = 0.0_wp
399         IF ( ln_bias_rlx ) THEN
400            tbias_rlx(:,:,:) = 0.0_wp
401            sbias_rlx(:,:,:) = 0.0_wp
402         ENDIF
403         IF ( ln_bias_asm ) THEN   !now rlx and asm bias in same file
404           tbias_asm(:,:,:) = 0.0_wp
405           sbias_asm(:,:,:) = 0.0_wp
406         ENDIF
407
408         IF ( ln_incpc ) THEN   !incr pressure correction
409           tbias_asm_stscale(:,:,:) = 0.0_wp
410           sbias_asm_stscale(:,:,:) = 0.0_wp
411         ENDIF
412
413
414         numbias_tot    = 0
415         ! Get bias from file and prevent fail if the file does not exist
416         IF(lwp) WRITE(numout,*) 'Opening ',TRIM( cn_bias_tot ) 
417         CALL iom_open( cn_bias_tot, numbias_tot, ldstop=.FALSE. )
418         
419         IF ( numbias_tot > 0 ) THEN     
420            ! Could check validity time of bias fields here...
421            ! Get the T and S bias data
422            IF(lwp) WRITE(numout,*) 'Reading bias fields from tot...'
423
424            !Search for bias from relaxation term if needed. Use same file
425            IF ( ln_bias_rlx ) THEN
426               IF(lwp) WRITE(numout,*) 'Reading bias fields for bias rlx from file ',cn_bias_tot
427               IF( iom_varid( numbias_tot, 'tbias_rlx' ) > 0 ) THEN
428                  ! Get the T and S bias data
429                  CALL iom_get( numbias_tot, jpdom_autoglo, 'tbias_rlx', tbias_rlx )
430                  CALL iom_get( numbias_tot, jpdom_autoglo, 'sbias_rlx', sbias_rlx )
431               ELSE
432                  CALL ctl_stop( 'Bias relaxation variables not found in ',cn_bias_tot )
433               ENDIF
434            ENDIF
435
436
437            !Search for bias from assim term if needed. Use same file
438            IF ( ln_bias_asm .and. .not.ln_bsyncro ) THEN
439               IF(lwp) WRITE(numout,*) 'Reading a-syncro bias fields for bias asm from file ',cn_bias_tot
440               IF( iom_varid( numbias_tot, 'tbias_asm' ) > 0 ) THEN
441                  ! Get the T and S bias data
442                  CALL iom_get( numbias_tot, jpdom_autoglo, 'tbias_asm', tbias_asm )
443                  CALL iom_get( numbias_tot, jpdom_autoglo, 'sbias_asm', sbias_asm )
444               ELSE
445                  CALL ctl_stop( 'Bias assim variables not found in ',cn_bias_tot )
446               ENDIF
447            ENDIF
448
449            IF ( ln_incpc .and. .not.ln_bsyncro ) THEN
450               IF(lwp) WRITE(numout,*) 'Reading short time scale bias correction fields for bias asm from file ',cn_bias_tot
451               IF( iom_varid( numbias_tot, 'tbias_asm_stscale' ) > 0 ) THEN
452                  ! Get the T and S bias data
453                  CALL iom_get( numbias_tot, jpdom_autoglo, 'tbias_asm_stscale', tbias_asm_stscale )
454                     CALL iom_get( numbias_tot, jpdom_autoglo, 'sbias_asm_stscale', sbias_asm_stscale )
455               ELSE
456                     CALL ctl_stop( 'Short time scale bias assim variables not found in ',cn_bias_tot )
457               ENDIF
458            ENDIF 
459
460
461
462            ! Close the file
463            CALL iom_close(numbias_tot)
464
465         ELSE
466            IF(lwp) WRITE(numout,*) 'No bias file found so T and S bias fields are set to zero'
467         ENDIF
468
469      ENDIF
470
471     ! for the time being, the bias_asm is read in the same file as
472     ! bias_rlx
473     ! Implications: bias_asm is estimated/evolved in time in the second outer
474     !               loop only, when the assimilation increments are ready.
475     !               bias_asm is kept cte during the first outer loop.
476     !              => Assyncronous bias correction.
477     ! Alternative: Syncronous bias correction:
478     !              bias_asm estimated/evolved in the first outer loop
479     !              with the asm incrments of the previous cycle.
480     !              bias_asm kept cte during the second outer loop.
481     !              Implication: bias_asm should be estimated really in the
482     !              inner loop.
483      IF ( ln_bsyncro ) THEN
484      ! Read bias from assimilation from a separate file
485      IF ( ln_bias_asm ) THEN
486         tbias_asm(:,:,:) = 0.0_wp
487         sbias_asm(:,:,:) = 0.0_wp
488         numbias_asm      = 0
489         ! Get bias from file and prevent fail if the file does not exist
490         IF(lwp) WRITE(numout,*) 'Opening file for syncro assim bias ',TRIM( cn_bias_asm ) 
491         CALL iom_open( cn_bias_asm, numbias_asm, ldstop=.FALSE. )
492         
493         IF ( numbias_asm > 0 ) THEN     
494            ! Could check validity time of bias fields here...
495           
496            ! Get the T and S bias data
497            IF(lwp) WRITE(numout,*) 'Reading syncro bias fields from asm from file ',cn_bias_asm
498            CALL iom_get( numbias_asm, jpdom_autoglo, 'tbias_asm', tbias_asm )
499            CALL iom_get( numbias_asm, jpdom_autoglo, 'sbias_asm', sbias_asm )
500           
501!  this is only applicable if tbias_asm were to be calculated in the inner loop
502            tbias_asm(:,:,:) = tbias_asm(:,:,:) * rdt / bias_time_unit_asm
503            sbias_asm(:,:,:) = sbias_asm(:,:,:) * rdt / bias_time_unit_asm
504           
505            ! Close the file
506            CALL iom_close(numbias_asm)
507           
508         ELSE
509            IF(lwp) WRITE(numout,*) 'No bias file found from asm so T and S bias fields are set to zero'
510         ENDIF
511         
512      ENDIF
513
514      ENDIF
515
516      !latitudinal dependence of partition coeficients. Adhoc
517      IF ( nn_lat_ramp == 1 ) THEN
518         ! Use the inertial ramp.
519         lenscl_bias = ( rn_maxlat_bias - rn_minlat_bias )*2._wp
520         WHERE ( abs( gphit(:,:) ) <= rn_minlat_bias )         
521            fbcoef(:,:) = 0._wp         
522         ELSEWHERE ( abs( gphit(:,:) ) >= rn_maxlat_bias )         
523            fbcoef(:,:) = 1._wp                   
524         ELSEWHERE       
525            fbcoef(:,:) = 1._wp - exp( -( abs( gphit(:,:) ) - rn_minlat_bias ) &
526                           * ( abs( gphit(:,:) ) - rn_minlat_bias ) / lenscl_bias )                         
527         ENDWHERE 
528      ELSEIF ( nn_lat_ramp == 2 ) THEN   
529         ! Use a linear ramp consist with the geostrophic velocity balance ramp in NEMOVAR
530     
531         WHERE ( abs( gphit(:,:) ) <= rn_minlat_bias )
532            fbcoef(:,:) = 0._wp
533         ELSEWHERE ( abs( gphit(:,:) ) >= rn_maxlat_bias ) 
534            fbcoef(:,:) = 1._wp
535         ELSEWHERE
536            fbcoef(:,:) = 1._wp - ((rn_maxlat_bias - abs( gphit(:,:)))/(rn_maxlat_bias - rn_minlat_bias))
537         ENDWHERE
538      ELSE
539         fbcoef(:,:) = 0.0_wp
540         fctamp      = 0.0_wp
541         fbcoef_stscale(:,:) = 0.0_wp
542      ENDIF
543
544
545      IF ( ln_incpc) THEN
546       ! not sure if this should be a special case of nn_lat_ramp == 2
547         minlat_bias = 3.0_wp
548         maxlat_bias = 8.0_wp 
549         WHERE ( abs( gphit(:,:) ) <= minlat_bias )
550            fbcoef_stscale(:,:)=0._wp
551         ELSEWHERE ( abs( gphit(:,:) ) >= maxlat_bias ) 
552            fbcoef_stscale(:,:)=1._wp
553         ELSEWHERE
554            fbcoef_stscale(:,:)=1._wp - ((maxlat_bias - abs( gphit(:,:)))/(maxlat_bias-minlat_bias))
555         ENDWHERE   
556      ENDIF
557
558
559   END SUBROUTINE bias_init
560
561   SUBROUTINE tra_bias ( kt )
562      !!----------------------------------------------------------------------
563      !!                    ***  ROUTINE tra_bias  ***
564      !!
565      !! ** Purpose : Update bias field every time step
566      !!
567      !! ** Method  : add contributions to bias from 3 terms
568      !!
569      !! ** Action  : Bias from assimilation (read in bias_init)
570      !!              Bias from relaxation term is estimated according to
571      !!              the prescribed time evolution of the bias
572      !!              Bias from ofl term is read from external file
573      !!              The difference contributions are added and the partition
574      !!              into direct bias in T/S and pressure perfomed.
575      !!
576      !! History :  09-03  (M. Balmaseda)
577      !!----------------------------------------------------------------------
578      !! called every timestep after dta_sst if ln_bias true.
579
580      IMPLICIT NONE
581
582      !! * Arguments
583      INTEGER, INTENT(IN) ::   kt             ! ocean time-step index
584      !! * Local variables
585      INTEGER             ::   ji,jj,jk, it   ! local loop index
586      REAL(wp)            ::   tsclf          ! time saling factor
587      REAL(wp)            ::   fb_t_asm_max, fb_t_rlx_max, fb_t_ofl_max
588      REAL(wp)            ::   ztfrac, ztsday
589      REAL(wp)            ::   zfrac, zfrac1 ! temporal weights for inst pcbias (names could be changed)
590      REAL(wp)            ::   zdecay        ! used in inst pcorr
591      REAL(wp), DIMENSION(jpi,jpj) :: zcof1, zcof2
592
593      IF ( .NOT. ln_bias ) RETURN
594      fb_t_rlx_max   = MIN(fb_t_rlx*fctamp,1.0_wp)
595      fb_t_asm_max   = MIN(fb_t_asm*fctamp,1.0_wp)
596      fb_t_ofl_max   = MIN(fb_t_ofl*fctamp,1.0_wp)
597
598      tbias(:,:,:)   = 0.0_wp
599      sbias(:,:,:)   = 0.0_wp
600      tbias_p(:,:,:) = 0.0_wp
601      sbias_p(:,:,:) = 0.0_wp
602      tbias_i(:,:,:) = 0.0_wp
603      sbias_i(:,:,:) = 0.0_wp
604
605      IF ( ln_bias_asm ) THEN
606     
607         tsclf = 1
608         IF ( .NOT.ln_bsyncro ) tsclf = rdt / bias_time_unit_asm 
609         zcof1(:,:) = tsclf * ( ( 1.0_wp - fbcoef(:,:) ) * fb_t_asm + &
610            &                              fbcoef(:,:)   * fb_t_asm_max )
611         zcof2(:,:) = ( 1.0_wp - fbcoef(:,:) ) * fb_p_asm
612     
613
614         IF ( ln_itdecay ) THEN   !decay the pressure correction at each time step
615   
616       ztsday  = rday / real(rdt)
617
618            zdecay = (1-ztscale)**(1/real(ztsday)) ! used in ipc
619            zfrac1 = zdecay**real(kt) ! used in ipc
620            IF ( zfrac1 <= 0.0 ) zfrac1 = 0.0_wp
621
622
623            IF( ln_asmiau .and. ln_trainc ) THEN  ! nudge in increments and decay historical contribution
624
625               
626               IF ( kt <= nitiaufin ) THEN  ! During IAU calculate the fraction of increments to apply at each time step
627
628                  ztfrac = real(kt) / real(nitiaufin)  ! nudging factor during the IAU
629                 
630         
631                  IF (lwp) THEN
632                     WRITE(numout,*) 'tra_bias : bias weights'
633                     WRITE(numout,*) '~~~~~~~~~~~~'
634                     WRITE(numout,* ) "proportion of  increment applied in pcbias ",ztfrac
635                     WRITE(numout,* ) "proportion of  historical pcbias applied ",t_asm_mem**(real(kt)/ztsday)
636                  ENDIF
637
638
639                  DO jk = 1, jpkm1
640                     
641                     tbias(:,:,jk) = tbias(:,:,jk) +                            &
642                     &                ( t_asm_mem**(real(kt)/ztsday) * tbias_asm(:,:,jk)  +                    &
643                     &                ztfrac * t_asm_upd * t_bkginc(:,:,jk) * tmask(:,:,jk) ) * zcof1(:,:)
644                     sbias(:,:,jk) = sbias(:,:,jk) +                            &
645                     &               ( t_asm_mem**(real(kt)/ztsday) * sbias_asm(:,:,jk)  +                     &
646                     &               ztfrac * t_asm_upd * s_bkginc(:,:,jk) * tmask(:,:,jk) ) * zcof1(:,:)
647                     tbias_p(:,:,jk) = tbias_p(:,:,jk) +                        &
648                     &               ( t_asm_mem**(real(kt)/ztsday) * tbias_asm(:,:,jk)  +                     &
649                     &               ztfrac * t_asm_upd * t_bkginc(:,:,jk) * tmask(:,:,jk) ) * zcof2(:,:)
650                     sbias_p(:,:,jk) = sbias_p(:,:,jk) +                        & 
651                     &               ( t_asm_mem**(real(kt)/ztsday) * sbias_asm(:,:,jk)  +                     &
652                     &               ztfrac * t_asm_upd * s_bkginc(:,:,jk) * tmask(:,:,jk) ) * zcof2(:,:)
653                  ENDDO
654
655
656                  IF (ln_incpc) THEN
657
658
659                     IF (lwp) THEN
660                       WRITE(numout,*) 'tra_bias : bias weights'
661                       WRITE(numout,*) '~~~~~~~~~~~~'
662                       WRITE(numout,* ) "IPC - proportion of  increment applied in pcbias ",ztfrac
663                       WRITE(numout,* ) "IPC - proportion of  historical pcbias applied ",zfrac1
664                     ENDIF
665
666                     DO jk = 1, jpkm1
667
668                        tbias_i(:,:,jk) =  ( t_bkginc(:,:,jk) * tmask(:,:,jk)* zwgt * ztfrac * (1.0 - fbcoef_stscale(:,:)) )         &
669                        &                + ( tbias_asm_stscale(:,:,jk) * zfrac1 * (1.0 - fbcoef_stscale(:,:)) )
670                        sbias_i(:,:,jk) =  ( s_bkginc(:,:,jk) * tmask(:,:,jk)* zwgt * ztfrac * (1.0 - fbcoef_stscale(:,:)) )         &
671                        &                + ( sbias_asm_stscale(:,:,jk) * zfrac1 * (1.0 - fbcoef_stscale(:,:)) )
672
673                     ENDDO
674
675                  ENDIF
676
677                  IF ( .not.ln_bsyncro ) THEN
678
679                     IF ( kt == nn_bias_itwrt ) THEN
680
681                        DO jk = 1, jpkm1
682                           tbias_asm_out(:,:,jk) =  t_asm_mem**(real(kt)/ztsday) * tbias_asm(:,:,jk)  +       &
683                           &                     ztfrac * t_asm_upd * t_bkginc(:,:,jk) * tmask(:,:,jk)
684                           sbias_asm_out(:,:,jk) =  t_asm_mem**(real(kt)/ztsday) * sbias_asm(:,:,jk)  +       &
685                           &                     ztfrac * t_asm_upd * s_bkginc(:,:,jk) * tmask(:,:,jk)
686                         END DO
687
688                        IF ( ln_incpc) THEN
689                           DO jk = 1, jpkm1
690                              tbias_asm_stscale_out(:,:,jk) = ( t_bkginc(:,:,jk) * tmask(:,:,jk) *  zwgt * ztfrac ) + ( tbias_asm_stscale(:,:,jk) * zfrac1 )
691                              sbias_asm_stscale_out(:,:,jk) = ( s_bkginc(:,:,jk) * tmask(:,:,jk) *  zwgt * ztfrac ) + ( sbias_asm_stscale(:,:,jk) * zfrac1 )
692                           ENDDO
693                        ENDIF
694
695                     ENDIF
696
697                  ENDIF
698
699                  ! update the historical component with the increments at the end of the IAU
700                  IF ( kt == nitiaufin ) THEN
701                     DO jk = 1, jpkm1
702                        tbias_asm(:,:,jk) =  t_asm_mem**(real(kt)/ztsday) * tbias_asm(:,:,jk)  +       &
703                        &                     ztfrac * t_asm_upd * t_bkginc(:,:,jk) * tmask(:,:,jk)
704                        sbias_asm(:,:,jk) =  t_asm_mem**(real(kt)/ztsday) * sbias_asm(:,:,jk)  +       &
705                        &                     ztfrac * t_asm_upd * s_bkginc(:,:,jk) * tmask(:,:,jk)
706                     END DO
707
708                     IF (ln_incpc) THEN
709                        DO jk = 1, jpkm1
710                           tbias_asm_stscale(:,:,jk) = ( t_bkginc(:,:,jk) * tmask(:,:,jk) * zwgt * ztfrac ) + ( tbias_asm_stscale(:,:,jk) * zfrac1 )
711                           sbias_asm_stscale(:,:,jk) = ( s_bkginc(:,:,jk) * tmask(:,:,jk) * zwgt * ztfrac ) + ( sbias_asm_stscale(:,:,jk) * zfrac1 )
712                        ENDDO
713                     ENDIF
714     
715                  ENDIF
716
717               
718               ELSE ! decay pressure correction from combined historical component and increments after IAU
719
720                  ztfrac=t_asm_mem**(real(kt-nitiaufin)/real(nitiaufin))  ! decay from end of IAU
721                 
722                 
723                  DO jk = 1, jpkm1
724                     tbias(:,:,jk) = tbias(:,:,jk) +                            &
725                     &                ( ztfrac * tbias_asm(:,:,jk) ) * zcof1(:,:)
726                     sbias(:,:,jk) = sbias(:,:,jk) +                            &
727                     &               (  ztfrac * sbias_asm(:,:,jk) ) * zcof1(:,:)
728                     tbias_p(:,:,jk) = tbias_p(:,:,jk) +                        &
729                     &               (  ztfrac * tbias_asm(:,:,jk) ) * zcof2(:,:)
730                     sbias_p(:,:,jk) = sbias_p(:,:,jk) +                        & 
731                     &               ( ztfrac * sbias_asm(:,:,jk) ) * zcof2(:,:)
732
733                  ENDDO
734
735                 IF (ln_incpc) THEN
736
737                   zfrac  = zdecay**real(kt-nitiaufin) 
738                   IF ( zfrac <= 0.0 ) zfrac = 0.0_wp
739   
740
741                   DO jk = 1, jpkm1
742                      tbias_i(:,:,jk) =  tbias_asm_stscale(:,:,jk) * zfrac * (1.0 - fbcoef_stscale(:,:))
743                      sbias_i(:,:,jk) =  sbias_asm_stscale(:,:,jk) * zfrac * (1.0 - fbcoef_stscale(:,:))
744                   ENDDO
745
746                   IF (lwp) THEN
747                     WRITE(numout,*) 'tra_bias : bias weights'
748                     WRITE(numout,*) '~~~~~~~~~~~~'
749                     WRITE(numout,* ) "IPC - proportion of increments + historical pcbias applied ",zfrac
750                   ENDIF
751
752                 ENDIF
753
754                  IF (lwp) THEN
755                     WRITE(numout,*) 'tra_bias : bias weights'
756                     WRITE(numout,*) '~~~~~~~~~~~~'
757                     WRITE(numout,* ) "proportion of increments + historical pcbias applied ",ztfrac
758                  ENDIF
759
760                  IF ( ln_trainc .and. .not.ln_bsyncro ) THEN
761                     IF ( kt == nn_bias_itwrt ) THEN
762                        DO jk = 1, jpkm1
763                           tbias_asm_out(:,:,jk) =  ztfrac * tbias_asm(:,:,jk) 
764                           sbias_asm_out(:,:,jk) =  ztfrac * sbias_asm(:,:,jk) 
765                        END DO
766
767                        IF ( ln_incpc ) THEN
768                           DO jk = 1, jpkm1
769                              tbias_asm_stscale_out(:,:,jk) =  tbias_asm_stscale(:,:,jk) * zfrac
770                              sbias_asm_stscale_out(:,:,jk) =  sbias_asm_stscale(:,:,jk) * zfrac
771                           ENDDO
772                        ENDIF
773
774                     ENDIF
775
776                  ENDIF
777
778               ENDIF
779
780
781            ELSE ! no assimilation increments, simply decay pressure correction (e.g for forecasts)
782
783               DO jk = 1, jpkm1
784                  tbias(:,:,jk) = tbias(:,:,jk) +                                                         &
785                  &               ( t_asm_mem**(real(kt)/ztsday) * tbias_asm(:,:,jk) ) * zcof1(:,:)
786                  sbias(:,:,jk) = sbias(:,:,jk) +                                                         &
787                  &               ( t_asm_mem**(real(kt)/ztsday) * sbias_asm(:,:,jk) ) * zcof1(:,:)
788                  tbias_p(:,:,jk) = tbias_p(:,:,jk) +                                                     &
789                  &               ( t_asm_mem**(real(kt)/ztsday) * tbias_asm(:,:,jk) ) * zcof2(:,:)
790                  sbias_p(:,:,jk) = sbias_p(:,:,jk) +                                                     & 
791                  &               ( t_asm_mem**(real(kt)/ztsday) * sbias_asm(:,:,jk) ) * zcof2(:,:)
792               ENDDO
793
794               IF (lwp) THEN
795                  WRITE(numout,*) 'tra_bias : bias weights'
796                  WRITE(numout,*) '~~~~~~~~~~~~'
797                  WRITE(numout,* ) "proportion of historical pcbias applied ",t_asm_mem**(real(kt)/ztsday)
798               ENDIF
799
800
801
802               IF (ln_incpc) THEN
803                 
804                   DO jk = 1, jpkm1
805                      tbias_i(:,:,jk) = ( tbias_asm_stscale(:,:,jk) * zfrac1 * (1.0 - fbcoef_stscale(:,:)) )
806                      sbias_i(:,:,jk) = ( sbias_asm_stscale(:,:,jk) * zfrac1 * (1.0 - fbcoef_stscale(:,:)) )
807                   ENDDO
808
809                   IF ( kt == nn_bias_itwrt ) THEN
810                      DO jk = 1, jpkm1
811                         tbias_asm_stscale_out(:,:,jk) = ( tbias_asm_stscale(:,:,jk) * zfrac1 )
812                         sbias_asm_stscale_out(:,:,jk) = ( sbias_asm_stscale(:,:,jk) * zfrac1 )
813                      ENDDO
814                   ENDIF
815
816               ENDIF
817
818
819
820
821            ENDIF
822 
823         ELSE ! maintain a constant pressure correction 
824
825            DO jk = 1, jpkm1
826               tbias(:,:,jk) = tbias(:,:,jk) + tbias_asm(:,:,jk) * zcof1(:,:)
827               sbias(:,:,jk) = sbias(:,:,jk) + sbias_asm(:,:,jk) * zcof1(:,:)
828               tbias_p(:,:,jk) = tbias_p(:,:,jk) + tbias_asm(:,:,jk) * zcof2(:,:)
829               sbias_p(:,:,jk) = sbias_p(:,:,jk) + sbias_asm(:,:,jk) * zcof2(:,:)
830            END DO     
831
832            IF( ln_asmiau .and. ln_trainc .and. .not.ln_bsyncro ) THEN   
833            ! if last outer loop (ln_asmiau=true and ln_trainc=true). t/sbias_asm
834            ! is updated, only once (end of run) taking into account units.
835               IF ( kt == nn_bias_itwrt ) THEN
836                 IF(lwp) WRITE(numout,*)' estimating asm bias at timestep: ',kt
837                 DO jk = 1, jpkm1
838                   tbias_asm_out(:,:,jk) = t_asm_mem * tbias_asm(:,:,jk)  +             &
839                   &                      t_asm_upd * t_bkginc(:,:,jk) * tmask(:,:,jk)
840                   sbias_asm_out(:,:,jk) = t_asm_mem * sbias_asm(:,:,jk) +             &
841                   &                      t_asm_upd * s_bkginc(:,:,jk) * tmask(:,:,jk)               
842                 END DO
843               ENDIF
844             ENDIF
845 
846         ENDIF
847
848      ENDIF
849
850
851#if   defined key_tradmp 
852      ! Time evolution of bias from relaxation
853      IF ( ln_bias_rlx ) THEN
854         tbias_rlx(:,:,:) = t_rlx_mem * tbias_rlx(:,:,:) + &
855            &               t_rlx_upd * ttrdmp(:,:,:) * rdt
856         sbias_rlx(:,:,:) = t_rlx_mem * sbias_rlx(:,:,:) + &
857            &               t_rlx_upd * strdmp(:,:,:) * rdt
858         zcof1(:,:) = ( 1.0_wp - fbcoef(:,:) ) * fb_t_rlx +      &
859            &                    fbcoef(:,:)   * fb_t_rlx_max
860         zcof2(:,:) = ( 1.0_wp - fbcoef(:,:) ) * fb_p_rlx
861         DO jk = 1, jpkm1
862            tbias(:,:,jk)   = tbias(:,:,jk) + tbias_rlx(:,:,jk) * zcof1(:,:)
863            sbias(:,:,jk)   = sbias(:,:,jk) + sbias_rlx(:,:,jk) * zcof1(:,:)
864            tbias_p(:,:,jk) = tbias_p(:,:,jk) + tbias_rlx(:,:,jk) * zcof2(:,:)
865            sbias_p(:,:,jk) = sbias_p(:,:,jk) + sbias_rlx(:,:,jk) * zcof2(:,:)
866         ENDDO
867         IF ( kt == nn_bias_itwrt ) THEN
868            tbias_rlx_out(:,:,:) = tbias_rlx(:,:,:)
869            sbias_rlx_out(:,:,:) = sbias_rlx(:,:,:)
870         ENDIF
871      ENDIF
872#endif
873      ! ofline bias
874      IF ( kt == nit000 ) THEN
875         IF(lwp) WRITE(numout,*) ' tra_bias: ln_bias_ofl = ',ln_bias_ofl
876         IF(lwp) WRITE(numout,*) ' ~~~~~~~~~'
877      ENDIF
878      IF ( ln_bias_ofl ) THEN
879         IF(lwp) WRITE(numout,*) 'reading offline bias'
880         CALL fld_read( kt, 1, sf_tbias_ofl ) 
881         CALL fld_read( kt, 1, sf_sbias_ofl ) 
882
883         zcof1(:,:) = ( 1.0_wp - fbcoef(:,:) ) * fb_t_ofl +           &
884            &                    fbcoef(:,:)   * fb_t_ofl_max
885         zcof2(:,:) = ( 1.0_wp - fbcoef(:,:) ) * fb_p_ofl
886         DO jk = 1, jpkm1
887            tbias(:,:,jk)   = tbias(:,:,jk) + sf_tbias_ofl(1)%fnow(:,:,jk) * zcof1(:,:)
888            sbias(:,:,jk)   = sbias(:,:,jk) + sf_sbias_ofl(1)%fnow(:,:,jk) * zcof1(:,:)
889            tbias_p(:,:,jk) = tbias_p(:,:,jk) + sf_tbias_ofl(1)%fnow(:,:,jk) * zcof2(:,:)
890            sbias_p(:,:,jk) = sbias_p(:,:,jk) + sf_sbias_ofl(1)%fnow(:,:,jk) * zcof2(:,:)
891         ENDDO
892      ENDIF
893
894
895      !apply bias on tracers if needed     
896      IF ( ln_bias_ts_app ) THEN
897         
898         ! Add the bias directely to T/s
899         tsa(:,:,:,jp_tem) = tsa(:,:,:,jp_tem) + tmask(:,:,:) * tbias(:,:,:) / rdt
900         tsa(:,:,:,jp_sal) = tsa(:,:,:,jp_sal) + tmask(:,:,:) * sbias(:,:,:) / rdt
901
902         ! lateral boundary conditions (is this needed?)
903         CALL lbc_lnk( tsa(:,:,:,jp_tem), 'T', 1.0_wp )
904         CALL lbc_lnk( tsa(:,:,:,jp_sal), 'T', 1.0_wp )   
905
906      ENDIF
907
908      IF ( kt == nn_bias_itwrt ) THEN
909         tbias_p_out(:,:,:)   = tbias_p(:,:,:)
910         sbias_p_out(:,:,:)   = sbias_p(:,:,:)
911         IF (ln_incpc) THEN
912            tbias_i_out(:,:,:)   = tbias_i(:,:,:)
913            sbias_i_out(:,:,:)   = sbias_i(:,:,:)
914         ENDIF
915      ENDIF
916
917   END SUBROUTINE tra_bias
918
919   SUBROUTINE dyn_bias( kt )
920      !!----------------------------------------------------------------------
921      !!                   ***  ROUTINE dyn_bias  ***
922      !!
923      !! ** Purpose :   Computes rhd_pc, gru/v_pc bias corrected
924      !!                for hydrostatic pressure gradient
925      !!                depending on time step (semi-implicit/centered)
926      !!                If partial steps computes bottom pressure gradient.
927      !!                These correction terms will affect only the dynamical
928      !!                component (pressure gradient calculation), but not
929      !!                the isopycnal calculation for the lateral mixing.
930      !!
931      !! ** Method  :   At this stage of the computation, ta and sa are the
932      !!                after temperature and salinity. If semi-implicit, these
933      !!                are used to compute rho and bottom pressure gradient.
934      !!                If centered, tb,sb are used instead.
935      !!                If bias key is activated, the temperature,salinity are
936      !!                bias corrected in the calculation of the density fields
937      !!                used in the pressure gradient calculation.
938      !!
939      !!
940      !! ** Action  : - rhd_pc ready. rhop will be overwriten later
941      !!              - if ln_zps, bottom density gradients gru/v_pc ready.
942      !!----------------------------------------------------------------------
943      !!
944      !! * Arguments
945      INTEGER, INTENT(IN) ::   kt    ! ocean time-step index
946      !! * Local variables
947      REAL(wp) :: tsw(jpi,jpj,jpk,jpts)
948      !!
949      !!----------------------------------------------------------------------
950      !
951      ! gtu,gsu,gtv,gsv rhop will be overwritten later in step.
952      !
953      IF( ln_dynhpg_imp  ) THEN                             ! semi-implicit hpg
954         tsw(:,:,:,jp_tem) = tsa(:,:,:,jp_tem) - tbias_p(:,:,:)
955         tsw(:,:,:,jp_sal) = tsa(:,:,:,jp_sal) - sbias_p(:,:,:)
956         IF ( ln_incpc ) THEN
957            tsw(:,:,:,jp_tem) = tsa(:,:,:,jp_tem) - tbias_p(:,:,:) - tbias_i(:,:,:)
958            tsw(:,:,:,jp_sal) = tsa(:,:,:,jp_sal) - sbias_p(:,:,:) - sbias_i(:,:,:)
959            IF ( ln_incpc_only ) THEN
960               tsw(:,:,:,jp_tem) = tsa(:,:,:,jp_tem) - tbias_i(:,:,:)
961               tsw(:,:,:,jp_sal) = tsa(:,:,:,jp_sal) - sbias_i(:,:,:)
962            ENDIF
963         ENDIF
964      ELSE
965         tsw(:,:,:,jp_tem) = tsb(:,:,:,jp_tem) - tbias_p(:,:,:)
966         tsw(:,:,:,jp_sal) = tsb(:,:,:,jp_sal) - sbias_p(:,:,:)
967         IF ( ln_incpc ) THEN
968            tsw(:,:,:,jp_tem) = tsb(:,:,:,jp_tem) - tbias_p(:,:,:) - tbias_i(:,:,:)
969            tsw(:,:,:,jp_sal) = tsb(:,:,:,jp_sal) - sbias_p(:,:,:) - sbias_i(:,:,:)
970            IF ( ln_incpc_only ) THEN
971               tsw(:,:,:,jp_tem) = tsb(:,:,:,jp_tem) - tbias_i(:,:,:)
972               tsw(:,:,:,jp_sal) = tsb(:,:,:,jp_sal) - sbias_i(:,:,:)
973            ENDIF
974         ENDIF
975      ENDIF
976
977      CALL eos( tsw, rhd_pc, rhop )
978     
979      ! is this needed?
980      CALL lbc_lnk( rhd_pc, 'T', 1.0_wp )
981
982      ! Partial steps: now horizontal gradient of t,s,rd
983      ! at the bottom ocean level
984      IF( ln_zps    )  THEN
985         CALL zps_hde( kt, jpts, tsw, gtsu, gtsv,  &
986            &          rhd_pc, gru_pc , grv_pc  )
987      ENDIF
988
989   END SUBROUTINE dyn_bias
990   
991   SUBROUTINE bias_opn( kt )
992      !!---------------------------------------------------------------------
993      !!                   ***  ROUTINE bias_opn  ***
994      !!                     
995      !! ** Purpose :  open bias restart file following the same logic as the
996      !!               standard restarts.
997      !!----------------------------------------------------------------------
998      !! * Arguments
999      INTEGER, INTENT(IN) ::   kt     ! ocean time-step
1000      !! * Local variables
1001      CHARACTER(LEN=20)   ::   clbkt    ! ocean time-step deine as a character
1002      CHARACTER(LEN=50)   ::   clbias_tot   ! total bias restart file name
1003      !!----------------------------------------------------------------------
1004      !
1005      IF( lrst_oce .AND. .NOT.lrst_bias ) THEN       ! create bias file
1006         IF( nitend > 999999999 ) THEN   ;   WRITE(clbkt, *       ) nitend
1007         ELSE                            ;   WRITE(clbkt, '(i8.8)') nitend
1008         ENDIF
1009         clbias_tot = TRIM(cexper)//"_"//TRIM(ADJUSTL(clbkt))//"_"//TRIM(cn_bias_tot)
1010         IF(lwp) THEN
1011            WRITE(numout,*)
1012            SELECT CASE ( jprstlib )
1013            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open tot bias restart binary file: '//clbias_tot
1014            CASE DEFAULT         ;   WRITE(numout,*) '             open tot bias restart NetCDF file: '//clbias_tot
1015            END SELECT
1016         ENDIF
1017         CALL iom_open( clbias_tot, numbias_tot , ldwrt = .TRUE., kiolib = jprstlib )
1018         lrst_bias=.TRUE.
1019
1020      ENDIF
1021      !
1022   END SUBROUTINE bias_opn
1023
1024   SUBROUTINE bias_wrt( kt )
1025      !!---------------------------------------------------------------------
1026      !!                   ***  ROUTINE bias_wrt  ***
1027      !!                     
1028      !! ** Purpose :   Write bias restart fields in the format corresponding to jprstlib
1029      !!
1030      !! ** Method  :   Write in numbias_tot when kt == nitend in output
1031      !!                file, save fields which are necessary for restart.
1032      !!
1033      !! Changed the timestep for writing to nitend rather than nitrst as this causes a
1034      !! problem if the nstock list is used to determine the restart output times and
1035      !! means that the bias is not output at all. M. Martin. 08/2011.
1036      !! Need to check with Magdalena that this is ok for ECMWF.
1037      !!----------------------------------------------------------------------
1038      !! * Arguments
1039      INTEGER, INTENT(IN) ::   kt   ! ocean time-step
1040      !!----------------------------------------------------------------------
1041      !                                                                     ! the begining of the run [s]
1042
1043      IF ( ln_bias_rlx ) THEN
1044         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'tbias_rlx' , tbias_rlx_out )   
1045         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'sbias_rlx' , sbias_rlx_out )   
1046      ENDIF
1047     
1048      IF ( ln_bias_asm ) THEN
1049         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'tbias_asm' , tbias_asm_out )   
1050         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'sbias_asm' , sbias_asm_out )   
1051         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'tbias_p'   , tbias_p_out )
1052         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'sbias_p'   , sbias_p_out )         
1053      ENDIF
1054
1055      IF ( ln_incpc ) THEN
1056         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'tbias_asm_stscale' , tbias_asm_stscale_out )   
1057         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'sbias_asm_stscale' , sbias_asm_stscale_out ) 
1058         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'tbias_i'   , tbias_i_out )
1059         CALL iom_rstput( nn_bias_itwrt, nn_bias_itwrt, numbias_tot, 'sbias_i'   , sbias_i_out )   
1060      ENDIF
1061     
1062      IF( kt == nitend ) THEN
1063         CALL iom_close( numbias_tot )     ! close the restart file (only at last time step)
1064         lrst_bias = .FALSE.
1065      ENDIF
1066      !
1067   END SUBROUTINE bias_wrt
1068
1069END MODULE bias
Note: See TracBrowser for help on using the repository browser.