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.
asmbkg.F90 in NEMO/trunk/src/OCE/ASM – NEMO

source: NEMO/trunk/src/OCE/ASM/asmbkg.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 7.9 KB
RevLine 
[3764]1MODULE asmbkg
2   !!======================================================================
3   !!                       ***  MODULE asmtrj -> asmbkg  ***
4   !! Assimilation trajectory interface: Write to file the background state and the model state trajectory
5   !!======================================================================
6   !! History :       ! 2007-03 (M. Martin)  Met. Office version
7   !!                 ! 2007-04 (A. Weaver)  asm_trj_wri, original code
8   !!                 ! 2007-03 (K. Mogensen)  Adapt to NEMOVAR and use IOM instead of IOIPSL
9   !!                 ! 2007-04 (A. Weaver)  Name change (formally asmbkg.F90). Distinguish
10   !!                                        background states in Jb term and at analysis time.
11   !!                                        Include state trajectory routine (currently empty)
12   !!                 ! 2007-07 (A. Weaver)  Add tke_rst and flt_rst for case nitbkg=0
13   !!                 ! 2009-03 (F. Vigilant)  Add hmlp (zdfmxl) for no tracer nmldp=2
14   !!                 ! 2009-06 (F. Vigilant) asm_trj_wri: special case when kt=nit000-1
15   !!                 ! 2009-07 (F. Vigilant) asm_trj_wri: add computation of eiv at restart
16   !!                 ! 2010-01 (A. Vidard) split asm_trj_wri into tam_trj_wri and asm_bkg_wri
17   !!----------------------------------------------------------------------
18
19   !!----------------------------------------------------------------------
20   !!   asm_bkg_wri  : Write out the background state
21   !!   asm_trj_wri  : Write out the model state trajectory (used with 4D-Var)
22   !!----------------------------------------------------------------------
23   USE oce                ! Dynamics and active tracers defined in memory
24   USE sbc_oce            ! Ocean surface boundary conditions
25   USE zdf_oce            ! Vertical mixing variables
26   USE zdfddm             ! Double diffusion mixing parameterization
[5836]27   USE ldftra             ! Lateral diffusion: eddy diffusivity coefficients
28   USE ldfslp             ! Lateral diffusion: slopes of neutral surfaces
[3764]29   USE tradmp             ! Tracer damping
30   USE zdftke             ! TKE vertical physics
31   USE eosbn2             ! Equation of state (eos_bn2 routine)
32   USE zdfmxl             ! Mixed layer depth
[6140]33   USE dom_oce     , ONLY :   ndastp
[3764]34   USE in_out_manager     ! I/O manager
35   USE iom                ! I/O module
36   USE asmpar             ! Parameters for the assmilation interface
37   USE zdfmxl             ! mixed layer depth
[9570]38#if defined key_si3
[3764]39   USE ice
40#endif
[6140]41
[3764]42   IMPLICIT NONE
43   PRIVATE
44   
45   PUBLIC   asm_bkg_wri   !: Write out the background state
46
47   !!----------------------------------------------------------------------
[9598]48   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[5215]49   !! $Id$
[10068]50   !! Software governed by the CeCILL license (see ./LICENSE)
[3764]51   !!----------------------------------------------------------------------
52CONTAINS
53
[12377]54   SUBROUTINE asm_bkg_wri( kt, Kmm )
[3764]55      !!-----------------------------------------------------------------------
56      !!                  ***  ROUTINE asm_bkg_wri ***
57      !!
58      !! ** Purpose : Write to file the background state for later use in the
59      !!              inner loop of data assimilation or for direct initialization
60      !!              in the outer loop.
61      !!
62      !! ** Method  : Write out the background state for use in the Jb term
63      !!              in the cost function and for use with direct initialization
64      !!              at analysis time.
65      !!-----------------------------------------------------------------------
66      INTEGER, INTENT( IN ) :: kt               ! Current time-step
[12377]67      INTEGER, INTENT( IN ) :: Kmm              ! time level index
[3764]68      !
69      CHARACTER (LEN=50) :: cl_asmbkg
70      CHARACTER (LEN=50) :: cl_asmdin
71      LOGICAL :: llok          ! Check if file exists
72      INTEGER :: inum          ! File unit number
73      REAL(wp) :: zdate        ! Date
74      !!-----------------------------------------------------------------------
75
76      !                                !-------------------------------------------
77      IF( kt == nitbkg_r ) THEN        ! Write out background at time step nitbkg_r
78         !                             !-----------------------------------========
79         !
80         WRITE(cl_asmbkg, FMT='(A,".nc")' ) TRIM( c_asmbkg )
81         cl_asmbkg = TRIM( cl_asmbkg )
82         INQUIRE( FILE = cl_asmbkg, EXIST = llok )
83         !
84         IF( .NOT. llok ) THEN
85            IF(lwp) WRITE(numout,*) ' Setting up assimilation background file '// TRIM( c_asmbkg )
86            !
87            !                                      ! Define the output file       
[10425]88            CALL iom_open( c_asmbkg, inum, ldwrt = .TRUE. )
[3764]89            !
90            IF( nitbkg_r == nit000 - 1 ) THEN      ! Treat special case when nitbkg = 0
91               zdate = REAL( ndastp )
[9019]92               IF( ln_zdftke ) THEN                   ! read turbulent kinetic energy ( en )
93                  IF(lwp) WRITE(numout,*) ' Reading TKE (en) from restart...'
94                  CALL tke_rst( nit000, 'READ' )
95               ENDIF
[3764]96            ELSE
97               zdate = REAL( ndastp )
98            ENDIF
99            !
100            !                                      ! Write the information
[12377]101            CALL iom_rstput( kt, nitbkg_r, inum, 'rdastp' , zdate                )
102            CALL iom_rstput( kt, nitbkg_r, inum, 'un'     , uu(:,:,:,Kmm)        )
103            CALL iom_rstput( kt, nitbkg_r, inum, 'vn'     , vv(:,:,:,Kmm)        )
104            CALL iom_rstput( kt, nitbkg_r, inum, 'tn'     , ts(:,:,:,jp_tem,Kmm) )
105            CALL iom_rstput( kt, nitbkg_r, inum, 'sn'     , ts(:,:,:,jp_sal,Kmm) )
106            CALL iom_rstput( kt, nitbkg_r, inum, 'sshn'   , ssh(:,:,Kmm)         )
107            IF( ln_zdftke )   CALL iom_rstput( kt, nitbkg_r, inum, 'en'     , en )
[3764]108            !
109            CALL iom_close( inum )
110         ENDIF
111         !
112      ENDIF
113
114      !                                !-------------------------------------------
115      IF( kt == nitdin_r ) THEN        ! Write out background at time step nitdin_r
116         !                             !-----------------------------------========
117         !
118         WRITE(cl_asmdin, FMT='(A,".nc")' ) TRIM( c_asmdin )
119         cl_asmdin = TRIM( cl_asmdin )
120         INQUIRE( FILE = cl_asmdin, EXIST = llok )
121         !
122         IF( .NOT. llok ) THEN
123            IF(lwp) WRITE(numout,*) ' Setting up assimilation background file '// TRIM( c_asmdin )
124            !
125            !                                      ! Define the output file       
[10425]126            CALL iom_open( c_asmdin, inum, ldwrt = .TRUE. )
[3764]127            !
128            IF( nitdin_r == nit000 - 1 ) THEN      ! Treat special case when nitbkg = 0
129
130               zdate = REAL( ndastp )
131            ELSE
132               zdate = REAL( ndastp )
133            ENDIF
134            !
135            !                                      ! Write the information
[12377]136            CALL iom_rstput( kt, nitdin_r, inum, 'rdastp' , zdate                )
137            CALL iom_rstput( kt, nitdin_r, inum, 'un'     , uu(:,:,:,Kmm)        )
138            CALL iom_rstput( kt, nitdin_r, inum, 'vn'     , vv(:,:,:,Kmm)        )
139            CALL iom_rstput( kt, nitdin_r, inum, 'tn'     , ts(:,:,:,jp_tem,Kmm) )
140            CALL iom_rstput( kt, nitdin_r, inum, 'sn'     , ts(:,:,:,jp_sal,Kmm) )
141            CALL iom_rstput( kt, nitdin_r, inum, 'sshn'   , ssh(:,:,Kmm)         )
[9570]142#if defined key_si3
[9019]143            IF( nn_ice == 2 ) THEN
144               IF( ALLOCATED(at_i) ) THEN
145                  CALL iom_rstput( kt, nitdin_r, inum, 'iceconc', at_i(:,:)   )
[4990]146               ELSE
[9019]147                  CALL ctl_warn('asm_bkg_wri: Ice concentration not written to background ',   &
148                     &          'as ice variable at_i not allocated on this timestep')
[5836]149               ENDIF
[3764]150            ENDIF
151#endif
152            !
153            CALL iom_close( inum )
154         ENDIF
155         !
156      ENDIF
157      !                   
158   END SUBROUTINE asm_bkg_wri
159
160   !!======================================================================
161END MODULE asmbkg
Note: See TracBrowser for help on using the repository browser.