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

source: branches/DEV_r2191_3partymerge2010/NEMO/OPA_SRC/ASM/asminc.F90 @ 2218

Last change on this file since 2218 was 2218, checked in by rblod, 14 years ago

Fix some 1D issues on DEV_r2191_3partymerge2010

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