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

source: branches/2011/dev_LOCEAN_CMCC_2011/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90 @ 3084

Last change on this file since 3084 was 3084, checked in by cetlod, 12 years ago

dev_LOCEAN_CMCC_2011: add in changes CMCC devlopments into the new branch

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