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/dev_1784_ASM/NEMO/OPA_SRC/ASM – NEMO

source: branches/dev_1784_ASM/NEMO/OPA_SRC/ASM/asminc.F90 @ 2002

Last change on this file since 2002 was 2002, checked in by djlea, 14 years ago

Adding ASM assimilation code

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