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

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90 @ 2588

Last change on this file since 2588 was 2435, checked in by cetlod, 14 years ago

Improve the 1D vertical configuration in v3.3beta

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