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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90 @ 2281

Last change on this file since 2281 was 2281, checked in by smasson, 14 years ago

set proper svn properties to all files...

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