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.
asminc.F90 in branches/devukmo2010/NEMO/OPA_SRC/ASM – NEMO

source: branches/devukmo2010/NEMO/OPA_SRC/ASM/asminc.F90 @ 2128

Last change on this file since 2128 was 2128, checked in by rfurner, 14 years ago

merged branches OBS, ASM, Rivers, BDY & mixed_dynldf ready for vn3.3 merge

File size: 37.2 KB
Line 
1MODULE asminc
2   !!======================================================================
3   !!                       ***  MODULE asminc  ***
4   !! Assimilation increment : Apply an increment generated by data
5   !!                          assimilation
6   !!======================================================================
7
8   !!----------------------------------------------------------------------
9   !!   'key_asminc' : Switch on the assimilation increment interface
10   !!----------------------------------------------------------------------
11   !!   asm_inc_init : Initialize the increment arrays and IAU weights
12   !!   calc_date    : Compute the calendar date YYYYMMDD on a given step
13   !!   tra_asm_inc  : Apply the tracer (T and S) increments
14   !!   dyn_asm_inc  : Apply the dynamic (u and v) increments
15   !!   ssh_asm_inc  : Apply the SSH increment
16   !!----------------------------------------------------------------------
17   !! * Modules used   
18   USE par_kind, ONLY : &       ! Precision variables
19      & wp
20   USE in_out_manager, ONLY : & ! I/O manager
21      & lwp,      &
22      & numnam,   &
23      & numout,   &
24      & ctl_warn, &
25      & ctl_stop, &
26      & nit000,   &
27      & nstop,    &
28      & ln_rstart
29   USE par_oce, ONLY : & ! Ocean space and time domain variables
30      & jpi,  & 
31      & jpj,  &
32      & jpk,  &
33      & jpkm1
34   USE dom_oce, ONLY : & ! Ocean space and time domain
35      & rdt,    &
36      & n_cla,  &
37      & neuler, &
38      & ln_zps, &
39      & tmask,  &
40      & umask,  &
41      & vmask
42   USE c1d, ONLY : &    ! 1D initialization
43      & lk_c1d
44   USE oce, ONLY : &      ! Dynamics and active tracers defined in memory
45      & ub, un, ua,    &
46      & vb, vn, va,    &
47      & tb, tn, ta,    &
48      & sb, sn, sa,    &
49      & sshb, sshn,    &
50      & rhd, rhop,     &
51      & rotb, rotn,    &
52      & hdivb, hdivn,  &
53      & gtu, gsu, gru, &
54      & gtv, gsv, grv 
55   USE divcur, ONLY : &   ! Horizontal divergence and relative vorticity
56      & div_cur
57   USE cla_div, ONLY : &  ! Specific update of the horizontal divergence
58      & div_cla           ! (specific to ORCA_R2)
59   USE eosbn2, ONLY : &   ! Equation of state - in situ and potential density
60      & eos
61   USE zpshde, ONLY : &   ! Partial step : Horizontal Derivative
62      & zps_hde
63!   USE phycst, ONLY : &   ! Calendar parameters
64!      & rjjss 
65   USE iom                ! Library to read input files
66   USE asmpar             ! Parameters for the assmilation interface
67   USE dom_oce, ONLY : &
68      & ndastp
69!   USE daymod, ONLY : &
70!      & nmonth_len         ! length of month in days
71!      & nbiss, &
72!      & nobis, &
73 
74
75   IMPLICIT NONE
76
77   !! * Routine accessibility
78   PRIVATE
79   PUBLIC asm_inc_init, & !: Initialize the increment arrays and IAU weights
80      &   calc_date,    & !: Compute the calendar date YYYYMMDD on a given step
81      &   tra_asm_inc,  & !: Apply the tracer (T and S) increments
82      &   dyn_asm_inc,  & !: Apply the dynamic (u and v) increments
83      &   ssh_asm_inc     !: Apply the SSH increment
84
85   !! * Private Module variables
86   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE :: &
87      & t_bkg,    &       !: Background temperature
88      & s_bkg,    &       !: Background salinity
89      & u_bkg,    &       !: Background u-component velocity
90      & v_bkg,    &       !: Background v-component velocity
91      & t_bkginc, &       !: Increment to the background temperature
92      & s_bkginc, &       !: Increment to the background salinity
93      & u_bkginc, &       !: Increment to the u-component velocity
94      & v_bkginc          !: Increment to the v-component velocity
95         
96   REAL(wp), PRIVATE, DIMENSION(:,:), ALLOCATABLE :: &
97      & ssh_bkg,   &      !: Background sea surface height
98      & ssh_bkginc        !: Increment to the background sea surface height
99
100   REAL(wp), PUBLIC, DIMENSION(:), ALLOCATABLE :: &
101      & wgtiau            !: IAU weights for each time step
102
103   !! * Shared Module variables
104   LOGICAL, PUBLIC, PARAMETER :: &
105#if defined key_asminc
106      & lk_asminc = .TRUE.   !: Logical switch for assimilation increment interface
107#else
108      & lk_asminc = .FALSE.  !: No assimilation increments
109#endif
110
111   LOGICAL, PUBLIC :: ln_bkgwri = .FALSE. !: No output of the background state fields
112   LOGICAL, PUBLIC :: ln_trjwri = .FALSE. !: No output of the state trajectory fields
113   LOGICAL, PUBLIC :: ln_asmiau = .FALSE. !: No applying forcing with an assimilation increment
114   LOGICAL, PUBLIC :: ln_asmdin = .FALSE. !: No direct initialization
115   LOGICAL, PUBLIC :: ln_trainc = .FALSE. !: No tracer (T and S) assimilation increments
116   LOGICAL, PUBLIC :: ln_dyninc = .FALSE. !: No dynamics (u and v) assimilation increments
117   LOGICAL, PUBLIC :: ln_sshinc = .FALSE. !: No sea surface height assimilation increment
118   LOGICAL, PUBLIC :: ln_salfix = .FALSE. !: Apply minimum salinity check
119
120   REAL, PUBLIC :: salfixmin   !: Ensure that the salinity is larger than
121   !                           !: this  value if (ln_salfix)
122#if defined key_asminc
123   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: &
124      & ssh_iau           !: IAU-weighted sea surface height increment
125#endif
126
127   INTEGER, PUBLIC :: nitbkg     !: Time step of the background state used in the Jb term
128                                 !: (relative to the cycle interval [0,nitend-nit000-1])
129   INTEGER, PUBLIC :: nitdin     !: Time step of the background state for direct initialization
130                                 !: (relative to the cycle interval [0,nitend-nit000-1])
131   INTEGER, PUBLIC :: nitiaustr  !: Time step of the start of the IAU interval
132                                 !: (relative to the cycle interval [0,nitend-nit000-1])
133   INTEGER, PUBLIC :: nitiaufin  !: Time step of the end of the IAU interval
134                                 !: (relative to the cycle interval [0,nitend-nit000-1])
135   INTEGER, PUBLIC :: niaufn     !: Type of IAU weighing function
136                                 !:   0 = Constant weighting
137                                 !:   1 = Linear hat-like, centred in middle of IAU interval
138
139CONTAINS
140
141   SUBROUTINE asm_inc_init
142      !!----------------------------------------------------------------------
143      !!                    ***  ROUTINE asm_inc_init  ***
144      !!         
145      !! ** Purpose : Initialize the assimilation increment and IAU weights.
146      !!
147      !! ** Method  : Initialize the assimilation increment and IAU weights.
148      !!
149      !! ** Action  :
150      !!
151      !! History :
152      !!        !  07-03  (M. Martin) Met Office version
153      !!        !  07-04  (A. Weaver) Merge with OPAVAR/NEMOVAR
154      !!----------------------------------------------------------------------
155
156      IMPLICIT NONE
157
158      !! * Modules used
159      NAMELIST/nam_asminc/ ln_bkgwri, ln_trjwri, &
160         &                 ln_trainc, ln_dyninc, ln_sshinc, &
161         &                 ln_asmdin, ln_asmiau, &
162         &                 nitbkg, nitdin, nitiaustr, nitiaufin, niaufn, &
163         &                 nittrjfrq, ln_salfix, salfixmin
164
165      !! * Local declarations
166      INTEGER :: jt
167
168      INTEGER :: imid
169      INTEGER :: inum
170      INTEGER :: iiauper         ! Number of time steps in the IAU period
171      INTEGER :: icycper         ! Number of time steps in the cycle
172      INTEGER :: iitend_date     ! Date YYYYMMDD of final time step
173      INTEGER :: iitbkg_date     ! Date YYYYMMDD of background time step for Jb term
174      INTEGER :: iitdin_date     ! Date YYYYMMDD of background time step for DI
175      INTEGER :: iitiaustr_date  ! Date YYYYMMDD of IAU interval start time step
176      INTEGER :: iitiaufin_date  ! Date YYYYMMDD of IAU interval final time step
177
178      REAL(wp) :: znorm        ! Normalization factor for IAU weights
179      REAL(wp) :: ztotwgt      ! Value of time-integrated IAU weights
180                               ! (should be equal to one)
181      REAL(wp) :: z_inc_dateb  ! Start date of interval on which increment is valid
182      REAL(wp) :: z_inc_datef  ! End date of interval on which increment is valid
183      REAL(wp) :: zdate_bkg    ! Date in background state file for DI
184      REAL(wp) :: zdate_inc    ! Time axis in increments file
185
186      !-----------------------------------------------------------------------
187      ! Read Namelist nam_asminc : assimilation increment interface
188      !-----------------------------------------------------------------------
189
190      ! Set default values
191      ln_bkgwri = .FALSE.
192      ln_trjwri = .FALSE.
193      ln_trainc = .FALSE.
194      ln_dyninc = .FALSE.
195      ln_sshinc = .FALSE.
196      ln_asmdin = .FALSE.
197      ln_asmiau = .TRUE.
198      ln_salfix = .FALSE.
199      salfixmin = -9999
200      nitbkg    = 0
201      nitdin    = 0     
202      nitiaustr = 1
203      nitiaufin = 150      ! = 10 days with ORCA2
204      niaufn    = 0
205      nittrjfrq = 1
206
207      REWIND ( numnam )
208      READ   ( numnam, nam_asminc )
209
210      ! Control print
211      IF(lwp) THEN
212         WRITE(numout,*)
213         WRITE(numout,*) 'asm_inc_init : Assimilation increment initialization :'
214         WRITE(numout,*) '~~~~~~~~~~~~'
215         WRITE(numout,*) '          Namelist namasm : set assimilation increment parameters'
216         WRITE(numout,*) '             Logical switch for writing out background state         ', &
217            &            ' ln_bkgwri = ', ln_bkgwri
218         WRITE(numout,*) '             Logical switch for writing out state trajectory         ', &
219            &            ' ln_trjwri = ', ln_trjwri
220         WRITE(numout,*) '             Logical switch for applying tracer increments           ', &
221            &            ' ln_trainc = ', ln_trainc
222         WRITE(numout,*) '             Logical switch for applying velocity increments         ', &
223            &            ' ln_dyninc = ', ln_dyninc
224         WRITE(numout,*) '             Logical switch for applying SSH increments              ', &
225            &            ' ln_sshinc = ', ln_sshinc
226         WRITE(numout,*) '             Logical switch for Direct Initialization (DI)           ', &
227            &            ' ln_asmdin = ', ln_asmdin
228         WRITE(numout,*) '             Logical switch for Incremental Analysis Updating (IAU)  ', &
229            &            ' ln_asmiau = ', ln_asmiau
230         WRITE(numout,*) '             Timestep of background in [0,nitend-nit000-1]           ', &
231            &            '    nitbkg = ', nitbkg
232         WRITE(numout,*) '             Timestep of background for DI in [0,nitend-nit000-1]    ', &
233            &            '    nitdin = ', nitdin
234         WRITE(numout,*) '             Timestep of start of IAU interval in [0,nitend-nit000-1]', &
235            &            ' nitiaustr = ', nitiaustr
236         WRITE(numout,*) '             Timestep of end of IAU interval in [0,nitend-nit000-1]  ', &
237            &            ' nitiaufin = ', nitiaufin
238         WRITE(numout,*) '             Type of IAU weighting function                          ', &
239            &            '    niaufn = ', niaufn
240         WRITE(numout,*) '             Frequency of trajectory output for 4D-VAR               ', &
241            &            ' nittrjfrq = ', nittrjfrq
242         WRITE(numout,*) '             Logical switch for ensuring that the sa > salfixmin     ', &
243            &            ' ln_salfix = ', ln_salfix
244         WRITE(numout,*) '             Minimum salinity after applying the increments          ', &
245            &            ' salfixmin = ', salfixmin
246      ENDIF
247
248      nitbkg_r    = nitbkg    + nit000 - 1  ! Background time referenced to nit000
249      nitdin_r    = nitdin    + nit000 - 1  ! Background time for DI referenced to nit000
250      nitiaustr_r = nitiaustr + nit000 - 1  ! Start of IAU interval referenced to nit000
251      nitiaufin_r = nitiaufin + nit000 - 1  ! End of IAU interval referenced to nit000
252
253      iiauper = nitiaufin_r - nitiaustr_r + 1  ! IAU interval length
254      icycper = nitend      - nit000      + 1  ! Cycle interval length
255
256      ! Date of final time step
257      CALL calc_date( nit000, nitend, ndate0, iitend_date )
258
259      ! Background time for Jb referenced to ndate0
260      CALL calc_date( nit000, nitbkg_r, ndate0, iitbkg_date )
261
262      ! Background time for DI referenced to ndate0
263      CALL calc_date( nit000, nitdin_r, ndate0, iitdin_date )
264
265      ! IAU start time referenced to ndate0
266      CALL calc_date( nit000, nitiaustr_r, ndate0, iitiaustr_date )
267
268      ! IAU end time referenced to ndate0
269      CALL calc_date( nit000, nitiaufin_r, ndate0, iitiaufin_date )
270
271      IF(lwp) THEN
272         WRITE(numout,*)
273         WRITE(numout,*) '   Time steps referenced to current cycle:'
274         WRITE(numout,*) '       iitrst      = ', nit000 - 1
275         WRITE(numout,*) '       nit000      = ', nit000
276         WRITE(numout,*) '       nitend      = ', nitend
277         WRITE(numout,*) '       nitbkg_r    = ', nitbkg_r
278         WRITE(numout,*) '       nitdin_r    = ', nitdin_r
279         WRITE(numout,*) '       nitiaustr_r = ', nitiaustr_r
280         WRITE(numout,*) '       nitiaufin_r = ', nitiaufin_r
281         WRITE(numout,*) '       nittrjfrq   = ', nittrjfrq
282         WRITE(numout,*)
283         WRITE(numout,*) '   Dates referenced to current cycle:'
284         WRITE(numout,*) '       ndastp         = ', ndastp
285         WRITE(numout,*) '       ndate0         = ', ndate0
286         WRITE(numout,*) '       iitend_date    = ', iitend_date
287         WRITE(numout,*) '       iitbkg_date    = ', iitbkg_date
288         WRITE(numout,*) '       iitdin_date    = ', iitdin_date
289         WRITE(numout,*) '       iitiaustr_date = ', iitiaustr_date
290         WRITE(numout,*) '       iitiaufin_date = ', iitiaufin_date
291      ENDIF
292
293      IF ( nacc /= 0 ) &
294         & CALL ctl_stop( ' nacc /= 0 and key_asminc :',  &
295         &                ' Assimilation increments have only been implemented', &
296         &                ' for synchronous time stepping' )
297
298      IF ( ( ln_asmdin ).AND.( ln_asmiau ) )   &
299         & CALL ctl_stop( ' ln_asmdin and ln_asmiau :', &
300         &                ' Choose Direct Initialization OR Incremental Analysis Updating')
301
302      IF (      ( ( .NOT. ln_asmdin ).AND.( .NOT. ln_asmiau ) ) &
303           .AND.( ( ln_trainc ).OR.( ln_dyninc ).OR.( ln_sshinc ) ) ) &
304         & CALL ctl_stop( ' One or more of ln_trainc, ln_dyninc and ln_sshinc is set to .true.', &
305         &                ' but ln_asmdin and ln_asmiau are both set to .false. :', &
306         &                ' Inconsistent options')
307
308      IF ( ( ln_bkgwri ).AND.( ( ln_asmdin ).OR.( ln_asmiau ) ) )  &
309         & CALL ctl_stop( ' ln_bkgwri and either ln_asmdin or ln_asmiau are set to .true.:', &
310         &                ' The background state must be written before applying the increments')
311
312      IF ( ( niaufn /= 0 ).AND.( niaufn /= 1 ) ) &
313         & CALL ctl_stop( ' niaufn /= 0 or niaufn /=1 :',  &
314         &                ' Type IAU weighting function is invalid')
315
316      IF ( ( .NOT. ln_trainc ).AND.( .NOT. ln_dyninc ).AND.( .NOT. ln_sshinc ) &
317         &                     )  &
318         & CALL ctl_warn( ' ln_trainc, ln_dyninc and ln_sshinc are set to .false. :', &
319         &                ' The assimilation increments are not applied')
320
321      IF ( ( ln_asmiau ).AND.( nitiaustr == nitiaufin ) ) &
322         & CALL ctl_stop( ' nitiaustr = nitiaufin :',  &
323         &                ' IAU interval is of zero length')
324
325      IF ( ( ln_asmiau ).AND.( ( nitiaustr_r < nit000 ).OR.( nitiaufin_r > nitend ) ) ) &
326         & CALL ctl_stop( ' nitiaustr or nitiaufin :',  &
327         &                ' IAU starting or final time step is outside the cycle interval', &
328         &                 ' Valid range nit000 to nitend')
329
330      IF ( ( nitbkg_r < nit000 - 1 ).OR.( nitbkg_r > nitend ) ) &
331         & CALL ctl_stop( ' nitbkg :',  &
332         &                ' Background time step is outside the cycle interval')
333
334      IF ( ( nitdin_r < nit000 - 1 ).OR.( nitdin_r > nitend ) ) &
335         & CALL ctl_stop( ' nitdin :',  &
336         &                ' Background time step for Direct Initialization is outside', &
337         &                ' the cycle interval')
338
339      IF ( nstop > 0 ) RETURN       ! if there are any errors then go no further
340
341      !--------------------------------------------------------------------
342      ! Initialize the Incremental Analysis Updating weighting function
343      !--------------------------------------------------------------------
344
345      IF ( ln_asmiau ) THEN
346
347         ALLOCATE( wgtiau( icycper ) )
348
349         wgtiau(:) = 0.0
350
351         IF ( niaufn == 0 ) THEN
352
353            !---------------------------------------------------------
354            ! Constant IAU forcing
355            !---------------------------------------------------------
356
357            DO jt = 1, iiauper
358               wgtiau(jt+nitiaustr-1) = 1.0 / REAL( iiauper )
359            END DO
360
361         ELSEIF ( niaufn == 1 ) THEN
362
363            !---------------------------------------------------------
364            ! Linear hat-like, centred in middle of IAU interval
365            !---------------------------------------------------------
366
367            ! Compute the normalization factor
368            znorm = 0.0
369            IF ( MOD( iiauper, 2 ) == 0 ) THEN  ! Even number of time steps in IAU interval
370               imid = iiauper / 2 
371               DO jt = 1, imid
372                  znorm = znorm + REAL( jt )
373               END DO
374               znorm = 2.0 * znorm
375            ELSE                               ! Odd number of time steps in IAU interval
376               imid = ( iiauper + 1 ) / 2       
377               DO jt = 1, imid - 1
378                  znorm = znorm + REAL( jt )
379               END DO
380               znorm = 2.0 * znorm + REAL( imid )
381            ENDIF
382            znorm = 1.0 / znorm
383
384            DO jt = 1, imid - 1
385               wgtiau(jt+nitiaustr-1) = REAL( jt ) * znorm
386            END DO
387            DO jt = imid, iiauper
388               wgtiau(jt+nitiaustr-1) = REAL( iiauper - jt + 1 ) * znorm
389            END DO
390
391         ENDIF
392
393         ! Test that the integral of the weights over the weighting interval equals 1
394          IF(lwp) THEN
395             WRITE(numout,*)
396             WRITE(numout,*) 'asm_inc_init : IAU weights'
397             WRITE(numout,*) '~~~~~~~~~~~~'
398             WRITE(numout,*) '             time step         IAU  weight'
399             WRITE(numout,*) '             =========     ====================='
400             ztotwgt = 0.0
401             DO jt = 1, icycper
402                ztotwgt = ztotwgt + wgtiau(jt)
403                WRITE(numout,*) '         ', jt, '       ', wgtiau(jt) 
404             END DO   
405             WRITE(numout,*) '         ==================================='
406             WRITE(numout,*) '         Time-integrated weight = ', ztotwgt
407             WRITE(numout,*) '         ==================================='
408          ENDIF
409         
410      ENDIF
411
412      !--------------------------------------------------------------------
413      ! Allocate and initialize the increment arrays
414      !--------------------------------------------------------------------
415
416      ALLOCATE( t_bkginc(jpi,jpj,jpk) )
417      ALLOCATE( s_bkginc(jpi,jpj,jpk) )
418      ALLOCATE( u_bkginc(jpi,jpj,jpk) )
419      ALLOCATE( v_bkginc(jpi,jpj,jpk) )
420      ALLOCATE( ssh_bkginc(jpi,jpj)   )
421#if defined key_asminc
422      ALLOCATE( ssh_iau(jpi,jpj)      )
423#endif
424      t_bkginc(:,:,:) = 0.0
425      s_bkginc(:,:,:) = 0.0
426      u_bkginc(:,:,:) = 0.0
427      v_bkginc(:,:,:) = 0.0
428      ssh_bkginc(:,:) = 0.0
429#if defined key_asminc
430      ssh_iau(:,:)    = 0.0
431#endif
432      IF ( ( ln_trainc ).OR.( ln_dyninc ).OR.( ln_sshinc ) ) THEN
433
434         !--------------------------------------------------------------------
435         ! Read the increments from file
436         !--------------------------------------------------------------------
437
438         CALL iom_open( c_asminc, inum )
439
440         CALL iom_get( inum, 'time', zdate_inc ) 
441
442         CALL iom_get( inum, 'z_inc_dateb', z_inc_dateb )
443         CALL iom_get( inum, 'z_inc_datef', z_inc_datef )
444         z_inc_dateb = zdate_inc
445         z_inc_datef = zdate_inc
446
447         IF(lwp) THEN
448            WRITE(numout,*) 
449            WRITE(numout,*) 'asm_inc_init : Assimilation increments valid ', &
450               &            ' between dates ', NINT( z_inc_dateb ),' and ',  &
451               &            NINT( z_inc_datef )
452            WRITE(numout,*) '~~~~~~~~~~~~'
453         ENDIF
454
455         IF (     ( NINT( z_inc_dateb ) < ndastp      ) &
456            & .OR.( NINT( z_inc_datef ) > iitend_date ) ) &
457            & CALL ctl_warn( ' Validity time of assimilation increments is ', &
458            &                ' outside the assimilation interval' )
459
460         IF ( ( ln_asmdin ).AND.( NINT( zdate_inc ) /= iitdin_date ) ) &
461            & CALL ctl_warn( ' Validity time of assimilation increments does ', &
462            &                ' not agree with Direct Initialization time' )
463
464         IF ( ln_trainc ) THEN   
465            CALL iom_get( inum, jpdom_autoglo, 'bckint', t_bkginc, 1 )
466            CALL iom_get( inum, jpdom_autoglo, 'bckins', s_bkginc, 1 )
467            ! Apply the masks
468            t_bkginc(:,:,:) = t_bkginc(:,:,:) * tmask(:,:,:)
469            s_bkginc(:,:,:) = s_bkginc(:,:,:) * tmask(:,:,:)
470            ! Set missing increments to 0.0 rather than 1e+20
471            ! to allow for differences in masks
472            WHERE( ABS( t_bkginc(:,:,:) ) > 1.0e+10 ) t_bkginc(:,:,:) = 0.0
473            WHERE( ABS( s_bkginc(:,:,:) ) > 1.0e+10 ) s_bkginc(:,:,:) = 0.0
474         ENDIF
475
476         IF ( ln_dyninc ) THEN   
477            CALL iom_get( inum, jpdom_autoglo, 'bckinu', u_bkginc, 1 )             
478            CALL iom_get( inum, jpdom_autoglo, 'bckinv', v_bkginc, 1 )             
479            ! Apply the masks
480            u_bkginc(:,:,:) = u_bkginc(:,:,:) * umask(:,:,:)
481            v_bkginc(:,:,:) = v_bkginc(:,:,:) * vmask(:,:,:)
482            ! Set missing increments to 0.0 rather than 1e+20
483            ! to allow for differences in masks
484            WHERE( ABS( u_bkginc(:,:,:) ) > 1.0e+10 ) u_bkginc(:,:,:) = 0.0
485            WHERE( ABS( v_bkginc(:,:,:) ) > 1.0e+10 ) v_bkginc(:,:,:) = 0.0
486         ENDIF
487       
488         IF ( ln_sshinc ) THEN
489            CALL iom_get( inum, jpdom_autoglo, 'bckineta', ssh_bkginc, 1 )
490            ! Apply the masks
491            ssh_bkginc(:,:) = ssh_bkginc(:,:) * tmask(:,:,1)
492            ! Set missing increments to 0.0 rather than 1e+20
493            ! to allow for differences in masks
494            WHERE( ABS( ssh_bkginc(:,:) ) > 1.0e+10 ) ssh_bkginc(:,:) = 0.0
495         ENDIF
496
497         CALL iom_close( inum )
498 
499      ENDIF
500
501      !-----------------------------------------------------------------------
502      ! Allocate and initialize the background state arrays
503      !-----------------------------------------------------------------------
504
505      IF ( ln_asmdin ) THEN
506
507         ALLOCATE( t_bkg(jpi,jpj,jpk) )
508         ALLOCATE( s_bkg(jpi,jpj,jpk) )
509         ALLOCATE( u_bkg(jpi,jpj,jpk) )
510         ALLOCATE( v_bkg(jpi,jpj,jpk) )
511         ALLOCATE( ssh_bkg(jpi,jpj)   )
512
513         t_bkg(:,:,:) = 0.0
514         s_bkg(:,:,:) = 0.0
515         u_bkg(:,:,:) = 0.0
516         v_bkg(:,:,:) = 0.0
517         ssh_bkg(:,:) = 0.0
518
519         !--------------------------------------------------------------------
520         ! Read from file the background state at analysis time
521         !--------------------------------------------------------------------
522
523         CALL iom_open( c_asmdin, inum )
524
525         CALL iom_get( inum, 'zdate', zdate_bkg ) 
526       
527         IF(lwp) THEN
528            WRITE(numout,*) 
529            WRITE(numout,*) 'asm_inc_init : Assimilation background state valid at : ', &
530               &  NINT( zdate_bkg )
531            WRITE(numout,*) '~~~~~~~~~~~~'
532         ENDIF
533
534         IF ( NINT( zdate_bkg ) /= iitdin_date ) &
535            & CALL ctl_warn( ' Validity time of assimilation background state does', &
536            &                ' not agree with Direct Initialization time' )
537
538         IF ( ln_trainc ) THEN   
539            CALL iom_get( inum, jpdom_autoglo, 'tn', t_bkg )
540            CALL iom_get( inum, jpdom_autoglo, 'sn', s_bkg )
541            t_bkg(:,:,:) = t_bkg(:,:,:) * tmask(:,:,:)
542            s_bkg(:,:,:) = s_bkg(:,:,:) * tmask(:,:,:)
543         ENDIF
544
545         IF ( ln_dyninc ) THEN   
546            CALL iom_get( inum, jpdom_autoglo, 'un', u_bkg )
547            CALL iom_get( inum, jpdom_autoglo, 'vn', v_bkg )
548            u_bkg(:,:,:) = u_bkg(:,:,:) * umask(:,:,:)
549            v_bkg(:,:,:) = v_bkg(:,:,:) * vmask(:,:,:)
550         ENDIF
551       
552         IF ( ln_sshinc ) THEN
553            CALL iom_get( inum, jpdom_autoglo, 'sshn', ssh_bkg )
554            ssh_bkg(:,:) = ssh_bkg(:,:) * tmask(:,:,1)
555         ENDIF
556
557         CALL iom_close( inum )
558
559      ENDIF
560
561   END SUBROUTINE asm_inc_init
562
563   SUBROUTINE calc_date( kit000, kt, kdate0, kdate )
564      !!----------------------------------------------------------------------
565      !!                    ***  ROUTINE calc_date  ***
566      !!         
567      !! ** Purpose : Compute the calendar date YYYYMMDD at a given time step.
568      !!
569      !! ** Method  : Compute the calendar date YYYYMMDD at a given time step.
570      !!
571      !! ** Action  :
572      !!
573      !! History :
574      !!        !  07-04  (A. Weaver)
575      !!        !  10-05  (D. Lea)        Update to work with NEMO vn3.2
576      !!----------------------------------------------------------------------
577
578      IMPLICIT NONE
579
580      !! * Arguments
581
582      INTEGER, INTENT(IN) :: kit000  ! Initial time step
583      INTEGER, INTENT(IN) :: kt      ! Current time step referenced to kit000
584      INTEGER, INTENT(IN) :: kdate0  ! Initial date
585      INTEGER, INTENT(OUT) :: kdate  ! Current date reference to kdate0
586
587      !! * Local declarations
588
589      INTEGER :: iyea0    ! Initial year
590      INTEGER :: imon0    ! Initial month
591      INTEGER :: iday0    ! Initial day
592      INTEGER :: iyea     ! Current year
593      INTEGER :: imon     ! Current month
594      INTEGER :: iday     ! Current day
595      INTEGER :: idaystp  ! Number of days between initial and current date
596      INTEGER :: idaycnt  ! Day counter
597
598      INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year
599
600      !-----------------------------------------------------------------------
601      ! Compute the calendar date YYYYMMDD
602      !-----------------------------------------------------------------------
603
604      ! Initial date
605      iyea0 =   kdate0 / 10000
606      imon0 = ( kdate0 - ( iyea0 * 10000 ) ) / 100
607      iday0 =   kdate0 - ( iyea0 * 10000 ) - ( imon0 * 100 ) 
608
609      ! Check that kt >= kit000 - 1
610      IF ( kt < kit000 - 1 ) CALL ctl_stop( ' kt must be >= kit000 - 1')
611
612      ! If kt = kit000 - 1 then set the date to the restart date
613      IF ( kt == kit000 - 1 ) THEN
614
615         kdate = ndastp
616         RETURN
617
618      ENDIF
619
620      ! Compute the number of days from the initial date
621      idaystp = INT( REAL( kt - kit000 ) * rdt / 86400. )
622   
623      iday    = iday0
624      imon    = imon0
625      iyea    = iyea0
626      idaycnt = 0
627
628      CALL calc_month_len( iyea, imonth_len )
629
630      DO WHILE ( idaycnt < idaystp )
631         iday = iday + 1
632         IF ( iday > imonth_len(imon) )  THEN
633            iday = 1
634            imon = imon + 1
635         ENDIF
636         IF ( imon > 12 ) THEN
637            imon = 1
638            iyea = iyea + 1
639            CALL calc_month_len( iyea, imonth_len )  ! update month lengths
640         ENDIF                 
641         idaycnt = idaycnt + 1
642      END DO
643
644      kdate = iyea * 10000 + imon * 100 + iday
645
646   END SUBROUTINE
647
648   SUBROUTINE calc_month_len( iyear, imonth_len )
649      !!----------------------------------------------------------------------
650      !!                    ***  ROUTINE calc_month_len  ***
651      !!         
652      !! ** Purpose : Compute the number of days in a months given a year.
653      !!
654      !! ** Method  :
655      !!
656      !! ** Action  :
657      !!
658      !! History :
659      !!        !  10-05  (D. Lea)   New routine based on day_init
660      !!----------------------------------------------------------------------
661
662      INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year
663      INTEGER :: iyear         !: year
664
665      ! length of the month of the current year (from nleapy, read in namelist)
666      IF ( nleapy < 2 ) THEN
667         imonth_len(:) = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /)
668         IF ( nleapy == 1 ) THEN   ! we are using calendar with leap years
669            IF ( MOD(iyear, 4) == 0 .AND. ( MOD(iyear, 400) == 0 .OR. MOD(iyear, 100) /= 0 ) ) THEN
670               imonth_len(2) = 29
671            ENDIF
672         ENDIF
673      ELSE
674         imonth_len(:) = nleapy   ! all months with nleapy days per year
675      ENDIF
676
677   END SUBROUTINE
678
679   SUBROUTINE tra_asm_inc( kt )
680      !!----------------------------------------------------------------------
681      !!                    ***  ROUTINE tra_asm_inc  ***
682      !!         
683      !! ** Purpose : Apply the tracer (T and S) assimilation increments
684      !!
685      !! ** Method  : Direct initialization or Incremental Analysis Updating
686      !!
687      !! ** Action  :
688      !!
689      !! History :
690      !!        !  07-03  (M. Martin) Met Office version
691      !!        !  07-04  (A. Weaver) Merge with OPAVAR/NEMOVAR
692      !!----------------------------------------------------------------------
693
694      IMPLICIT NONE
695
696      !! * Arguments
697      INTEGER, INTENT(IN) :: kt               ! Current time step
698
699      !! * Local declarations
700      INTEGER :: ji,jj,jk
701      INTEGER :: it
702      REAL(wp) :: zincwgt  ! IAU weight for current time step
703
704      IF ( ln_asmiau ) THEN
705
706         !--------------------------------------------------------------------
707         ! Incremental Analysis Updating
708         !--------------------------------------------------------------------
709
710         IF ( ( kt >= nitiaustr_r ).AND.( kt <= nitiaufin_r ) ) THEN
711
712            it = kt - nit000 + 1
713            zincwgt = wgtiau(it) / rdt   ! IAU weight for the current time step
714
715            IF(lwp) THEN
716               WRITE(numout,*) 
717               WRITE(numout,*) 'tra_asm_inc : Tracer IAU at time step = ', &
718                  &  kt,' with IAU weight = ', wgtiau(it)
719               WRITE(numout,*) '~~~~~~~~~~~~'
720            ENDIF
721
722            ! Update the tracer tendencies
723            DO jk = 1, jpkm1
724               ta(:,:,jk) = ta(:,:,jk) + t_bkginc(:,:,jk) * zincwgt 
725               sa(:,:,jk) = sa(:,:,jk) + s_bkginc(:,:,jk) * zincwgt
726            END DO
727
728            ! Salinity fix
729            IF (ln_salfix) THEN
730               DO jk = 1, jpkm1
731                  DO jj = 1, jpj
732                     DO ji= 1, jpi
733                        sa(ji,jj,jk) = MAX( sa(ji,jj,jk), salfixmin )
734                     END DO
735                  END DO
736               END DO
737            ENDIF
738
739         ENDIF
740
741         IF ( kt == nitiaufin_r + 1  ) THEN   ! For bias crcn to work
742            DEALLOCATE( t_bkginc )
743            DEALLOCATE( s_bkginc )
744         ENDIF
745
746
747      ELSEIF ( ln_asmdin ) THEN
748
749         !--------------------------------------------------------------------
750         ! Direct Initialization
751         !--------------------------------------------------------------------
752           
753         IF ( kt == nitdin_r ) THEN
754
755            neuler = 0  ! Force Euler forward step
756
757            ! Initialize the now fields with the background + increment
758            tn(:,:,:) = t_bkg(:,:,:) + t_bkginc(:,:,:)   
759            sn(:,:,:) = s_bkg(:,:,:) + s_bkginc(:,:,:)   
760
761            ! Optional salinity fix
762            IF (ln_salfix) THEN
763               DO jk = 1, jpkm1
764                  DO jj = 1, jpj
765                     DO ji= 1, jpi
766                        sn(ji,jj,jk) = MAX( sn(ji,jj,jk), salfixmin )
767                     END DO
768                  END DO
769               END DO
770            ENDIF
771
772            tb(:,:,:) = tn(:,:,:)                        ! Update before fields
773            sb(:,:,:) = sn(:,:,:)
774
775            CALL eos( tb, sb, rhd, rhop )                ! Before potential and in situ densities
776         
777            IF( ln_zps .AND. .NOT. lk_c1d ) &
778               &  CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before horizontal derivative
779               &                gtu, gsu, gru,        &  ! of T, S, rd at the bottom ocean level
780               &                gtv, gsv, grv )
781
782            DEALLOCATE( t_bkginc )
783            DEALLOCATE( s_bkginc )
784            DEALLOCATE( t_bkg    )
785            DEALLOCATE( s_bkg    )
786         ENDIF
787         
788      ENDIF
789
790   END SUBROUTINE tra_asm_inc
791
792   SUBROUTINE dyn_asm_inc( kt )
793      !!----------------------------------------------------------------------
794      !!                    ***  ROUTINE dyn_asm_inc  ***
795      !!         
796      !! ** Purpose : Apply the dynamics (u and v) assimilation increments.
797      !!
798      !! ** Method  : Direct initialization or Incremental Analysis Updating.
799      !!
800      !! ** Action  :
801      !!
802      !! History :
803      !!        !  07-03  (M. Martin) Met Office version
804      !!        !  07-04  (A. Weaver) Merge with OPAVAR/NEMOVAR
805      !!----------------------------------------------------------------------
806
807      IMPLICIT NONE
808
809      !! * Arguments
810      INTEGER, INTENT(IN) :: kt   ! Current time step
811
812      !! * Local declarations
813      INTEGER :: jk
814      INTEGER :: it
815      REAL(wp) :: zincwgt  ! IAU weight for current time step
816
817      IF ( ln_asmiau ) THEN
818
819         !--------------------------------------------------------------------
820         ! Incremental Analysis Updating
821         !--------------------------------------------------------------------
822
823         IF ( ( kt >= nitiaustr_r ).AND.( kt <= nitiaufin_r ) ) THEN
824
825            it = kt - nit000 + 1
826            zincwgt = wgtiau(it) / rdt   ! IAU weight for the current time step
827
828            IF(lwp) THEN
829               WRITE(numout,*) 
830               WRITE(numout,*) 'dyn_asm_inc : Dynamics IAU at time step = ', &
831                  &  kt,' with IAU weight = ', wgtiau(it)
832               WRITE(numout,*) '~~~~~~~~~~~~'
833            ENDIF
834
835            ! Update the dynamic tendencies
836            DO jk = 1, jpkm1
837               ua(:,:,jk) = ua(:,:,jk) + u_bkginc(:,:,jk) * zincwgt
838               va(:,:,jk) = va(:,:,jk) + v_bkginc(:,:,jk) * zincwgt
839            END DO
840           
841            IF ( kt == nitiaufin_r ) THEN
842               DEALLOCATE( u_bkginc )
843               DEALLOCATE( v_bkginc )
844            ENDIF
845
846         ENDIF
847
848      ELSEIF ( ln_asmdin ) THEN 
849
850         !--------------------------------------------------------------------
851         ! Direct Initialization
852         !--------------------------------------------------------------------
853         
854         IF ( kt == nitdin_r ) THEN
855
856            neuler = 0                    ! Force Euler forward step
857
858            ! Initialize the now fields with the background + increment
859            un(:,:,:) = u_bkg(:,:,:) + u_bkginc(:,:,:)
860            vn(:,:,:) = v_bkg(:,:,:) + v_bkginc(:,:,:) 
861
862            ub(:,:,:) = un(:,:,:)         ! Update before fields
863            vb(:,:,:) = vn(:,:,:)
864 
865            CALL div_cur( kt )                  ! Compute divergence and curl for now fields
866            IF( n_cla == 1 ) CALL div_cla( kt ) ! Cross Land Advection (Update Hor. divergence)
867
868            rotb (:,:,:) = rotn (:,:,:)   ! Update before fields
869            hdivb(:,:,:) = hdivn(:,:,:)
870
871            DEALLOCATE( u_bkg    )
872            DEALLOCATE( v_bkg    )
873            DEALLOCATE( u_bkginc )
874            DEALLOCATE( v_bkginc )
875
876         ENDIF
877
878      ENDIF
879
880   END SUBROUTINE dyn_asm_inc
881
882   SUBROUTINE ssh_asm_inc( kt )
883      !!----------------------------------------------------------------------
884      !!                    ***  ROUTINE ssh_asm_inc  ***
885      !!         
886      !! ** Purpose : Apply the sea surface height assimilation increment.
887      !!
888      !! ** Method  : Direct initialization or Incremental Analysis Updating.
889      !!
890      !! ** Action  :
891      !!
892      !! History :
893      !!        !  07-03  (M. Martin) Met Office version
894      !!        !  07-04  (A. Weaver) Merge with OPAVAR/NEMOVAR
895      !!----------------------------------------------------------------------
896
897      IMPLICIT NONE
898
899      !! * Arguments
900      INTEGER, INTENT(IN) :: kt   ! Current time step
901
902      !! * Local declarations
903      INTEGER :: it
904      REAL(wp) :: zincwgt  ! IAU weight for current time step
905
906      IF ( ln_asmiau ) THEN
907
908         !--------------------------------------------------------------------
909         ! Incremental Analysis Updating
910         !--------------------------------------------------------------------
911
912         IF ( ( kt >= nitiaustr_r ).AND.( kt <= nitiaufin_r ) ) THEN
913
914            it = kt - nit000 + 1
915            zincwgt = wgtiau(it) / rdt   ! IAU weight for the current time step
916
917            IF(lwp) THEN
918               WRITE(numout,*) 
919               WRITE(numout,*) 'ssh_asm_inc : SSH IAU at time step = ', &
920                  &  kt,' with IAU weight = ', wgtiau(it)
921               WRITE(numout,*) '~~~~~~~~~~~~'
922            ENDIF
923
924            ! Save the tendency associated with the IAU weighted SSH increment
925            ! (applied in dynspg.*)
926#if defined key_asminc
927            ssh_iau(:,:) = ssh_bkginc(:,:) * zincwgt
928#endif
929            IF ( kt == nitiaufin_r ) THEN
930               DEALLOCATE( ssh_bkginc )
931            ENDIF
932
933         ENDIF
934
935      ELSEIF ( ln_asmdin ) THEN
936
937         !--------------------------------------------------------------------
938         ! Direct Initialization
939         !--------------------------------------------------------------------
940
941         IF ( kt == nitdin_r ) THEN
942
943            neuler = 0                    ! Force Euler forward step
944
945            ! Initialize the now fields the background + increment
946            sshn(:,:) = ssh_bkg(:,:) + ssh_bkginc(:,:) 
947
948            sshb(:,:) = sshn(:,:)         ! Update before fields
949
950            DEALLOCATE( ssh_bkg    )
951            DEALLOCATE( ssh_bkginc )
952
953         ENDIF
954
955      ENDIF
956
957   END SUBROUTINE ssh_asm_inc
958
959END MODULE asminc
Note: See TracBrowser for help on using the repository browser.