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

source: trunk/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90 @ 2715

Last change on this file since 2715 was 2715, checked in by rblod, 13 years ago

First attempt to put dynamic allocation on the trunk

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