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.
nemotam.F90 in branches/TAM_V3_0/NEMOTAM/OPATAM_SRC – NEMO

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/nemotam.F90 @ 3400

Last change on this file since 3400 was 2587, checked in by vidard, 13 years ago

refer to ticket #798

  • Property svn:executable set to *
File size: 12.4 KB
Line 
1MODULE nemotam
2   !!==========================================================================
3   !!                       ***  MODULE nemovar ***
4   !! NEMOTAM system : Tangent and Adjoint for NEMO.
5   !!==========================================================================
6
7   !!----------------------------------------------------------------------
8   !!   nemotam_main   : Main driver routine for NEMOTAM
9   !!   nemotam_init   : Initialization of NEMOTAM
10   !!   nemotam_final  : Finish up NEMOTAM
11   !!----------------------------------------------------------------------
12   !! History :
13   !!   1.0  !  07-06  (K. Mogensen) Initial version
14   !!        !  09-06  (F. Vigilant)  Modified to split NEMOVAR / NEMOTAM
15   !!                                     module tamctl     i/o varctl
16   !!---------------------------------------------------------------------
17   !!----------------------------------------------------------------------
18   !! * Modules used
19   USE dom_oce         ! ocean space domain variables
20   USE lib_mpp         ! distributed memory computing
21   USE daymod          ! Date computations
22   USE in_out_manager  ! I/O manager
23   USE domcfg          ! domain configuration               (dom_cfg routine)
24   USE mppini          ! shared/distributed memory setting (mpp_init routine)
25   USE domain          ! domain initialization             (dom_init routine)
26   USE obc_par
27   USE obcini
28   USE phycst          ! physical constant                  (par_cst routine)
29   USE tamtrj          ! handling of the trajectory
30   USE trj_tam         ! handling of the trajectory
31   USE tamctl          ! Control parameters
32   USE oce_tam         ! TL and adjoint data
33   USE sbc_oce_tam     ! Surface BCs tangent and adjoint arrays
34   USE trc_oce_tam     ! Trend tangent and adjoint arrays
35   USE sol_oce_tam     ! Solver tangent and adjoint arrays
36   USE tamtst
37   ! ocean physics
38#if defined key_tam
39   USE ldfdyn        ! lateral viscosity setting  (ldfdyn_init routine)
40   USE ldftra        ! lateral diffusivity setting (ldftra_init routine)
41#endif
42   USE zdfini 
43
44#if defined key_tst_tlm
45#if defined key_tam
46   USE opatam_tst_ini, ONLY :  &
47     & opa_opatam_ini,          &
48     & opa_4_tst_ini,          &
49     & opatam_4_tst_ini
50#endif
51#endif
52
53   IMPLICIT NONE
54   PRIVATE
55
56   !! * Module variables
57
58   CHARACTER (len=64) ::        &
59      cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
60   LOGICAL, PUBLIC :: lini = .TRUE.         ! initialisation flag
61
62   !! * Routine accessibility
63
64   PUBLIC &
65      & nemotam_main,           &
66      & nemotam_banner   
67
68CONTAINS
69
70   SUBROUTINE nemotam_main 
71      !!----------------------------------------------------------------------
72      !!                    ***  ROUTINE nemotam_main  ***
73      !!         
74      !! ** Purpose : Main driver routine for NEMOTAM
75      !!
76      !! ** Method  : Nothing yet
77      !!
78      !! ** Action  : Nothing yet
79      !!
80      !! History :
81      !!        !  07-06  (K. Mogensen) Original code
82      !!----------------------------------------------------------------------
83
84      !! * Local declarations
85
86      ! Initialize grids and observations
87      CALL nemotam_root
88
89      ! Main inner loop
90      CALL nemotam_sub
91
92      ! Close all open files.
93      CALL nemotam_final
94
95   END SUBROUTINE nemotam_main
96
97   SUBROUTINE nemotam_init
98      !!----------------------------------------------------------------------
99      !!                    ***  ROUTINE nemotam_init  ***
100      !!         
101      !! ** Purpose : Initialize grids and read observations and background
102      !!
103      !! ** Method  : Read the namelist and call reading routines
104      !!
105      !! ** Action  : Read the namelist and call reading routines
106      !!
107      !! History :
108      !!        !  07-06  (K. Mogensen) Original code
109      !!        !  01-09  (A. Weaver) Include ocean physics initialization
110      !!----------------------------------------------------------------------
111
112      !! * Local declarations
113      CHARACTER (len=128) :: file_out = 'nemovar.output'
114      CHARACTER (len=*), PARAMETER  ::  namelistname = 'namelist.nemotam' 
115      NAMELIST/namctl/ ln_ctl, nprint, nictls, nictle,   &
116         &             isplt , jsplt , njctls, njctle, nbench, nbit_cmp
117
118      ! open listing and namelist units
119      CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
120         &         'SEQUENTIAL', 1, numout, .FALSE., 1 )
121      CALL nemotam_banner( numout )
122
123!      Commented as opening is done in Nemotam_root
124!      CALL ctlopn( numnam, namelistname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   &
125!         &           1, numout, .FALSE., 1 )
126
127      ! Namelist namctl : Control prints & Benchmark
128      REWIND( numnam )
129      READ  ( numnam, namctl )
130
131      ! Nodes selection
132      nproc = mynode()
133      narea = nproc + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
134      lwp   = narea == 1
135      ln_rstart = .FALSE.
136
137      ! open additionnal listing
138      IF( narea-1 > 0 )   THEN
139         WRITE(file_out,FMT="('nemotam.output_',I4.4)") narea-1
140         IF( numout /= 0 .AND. numout /= 6 ) THEN
141            CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
142               &         'SEQUENTIAL', 1, numout, .FALSE., 1 )
143         ENDIF
144         CALL nemotam_banner( numout )
145         lwp = .TRUE.
146         !
147      ENDIF     
148
149      IF(lwp) THEN
150         WRITE(numout,*)
151         WRITE(numout,*) 'nemotam_init: Control prints & Benchmark'
152         WRITE(numout,*) '~~~~~~~~~~~~ '
153         WRITE(numout,*) '          Namelist namctl'
154         WRITE(numout,*) '             run control (for debugging)     ln_ctl    = ', ln_ctl
155         WRITE(numout,*) '             level of print                  nprint    = ', nprint
156         WRITE(numout,*) '             bit comparison mode (0/1)       nbit_cmp  = ', nbit_cmp
157      ENDIF
158
159      IF( jpni*jpnj == jpnij ) THEN
160         CALL mpp_init                      ! standard cutting out
161      ELSE
162         CALL mpp_init2                     ! eliminate land processors
163      ENDIF
164     
165      CALL phy_cst                          ! Physical constants
166
167      CALL dom_cfg                          ! Domain configuration
168     
169      CALL dom_init                         ! Domain
170     
171      IF( lk_obc    )   CALL obc_init       ! Open boundaries
172
173      !                                     ! Ocean physics
174
175#if defined key_tam
176      CALL ldf_dyn_init                         ! Lateral ocean momentum physics
177
178      CALL ldf_tra_init                         ! Lateral ocean tracer physics
179#endif
180
181      CALL zdf_init                             ! Vertical ocean physics
182
183      CALL     oce_tam_init( 0 )            ! OCE TAM field
184      CALL sol_oce_tam_init( 0 )            ! Initialize elliptic solver
185      CALL trc_oce_tam_init( 0 )            ! TRC TAM fields
186#if defined key_tam
187      CALL sbc_oce_tam_init( 0 )            ! SBC TAM fields
188#endif
189      CALL     tam_trj_ini
190
191      CALL day_init
192      CALL day( nit000 )
193
194   END SUBROUTINE nemotam_init
195
196   SUBROUTINE nemotam_sub
197      !!----------------------------------------------------------------------
198      !!                    ***  ROUTINE nemotam_sub  ***
199      !!         
200      !! ** Purpose : Main driver routine for the NEMOTAM
201      !!
202      !! ** Method  :
203      !!
204      !! ** Action  :
205      !!
206      !! History :
207      !!        !  07-08  (K. Mogensen) Original code based on appvar.F.
208      !!----------------------------------------------------------------------
209
210      !! * Local declarations
211      NAMELIST/namtst/ ln_tst_nemotam, ln_tst_cpd_tam, ln_tst_stp_tam, &
212         &             ln_tst_tan_cpd, ln_tst_tan, ln_tst_stop
213
214      REAL(wp) :: &
215         & zcost,   &
216         & zcostf,  &
217         & zepsg,   &
218         & zctemp,  &
219         & zci_sim, &
220         & zgi_sim, &
221         & zcf_sim, &
222         & zgf_sim, &
223         & zcf_min, &
224         & zgf_min, &
225         & zcf_err, &
226         & zgf_err, &
227         & zcf_rel, &
228         & zgf_rel
229      INTEGER, DIMENSION(2) :: &
230         & izs
231      INTEGER :: &
232         & i_prec_vecs, &
233         & i_flag_rc,   &
234         & indic,       &
235         & ioutbef,     &
236         & iitr,        &
237         & isim,        &
238         & iabort
239      INTEGER :: &
240         & jnd1
241      CHARACTER(len=12) :: &
242         & clstp, &
243         & clend
244
245      i_flag_rc = 0
246
247      ln_tst_nemotam = .FALSE.
248      ln_tst_cpd_tam = .FALSE.
249      ln_tst_stp_tam = .FALSE.
250      ln_tst_tan_cpd = .FALSE.
251      ln_tst_tan     = .FALSE.
252      ln_tst_stop    = .FALSE.
253
254      REWIND( numnam )
255      READ  ( numnam, namtst )
256
257      IF(lwp) THEN
258
259         WRITE(numout,*) ' namtst'
260         WRITE(numout,*) ' '
261         WRITE(numout,*) ' switch for M adjoint tests   ln_tst_nemotam = ',ln_tst_nemotam
262         WRITE(numout,*) ' stop after tests                ln_tst_stop = ',ln_tst_stop
263         WRITE(numout,*) ' '
264
265      ENDIF
266
267      ! B.4 Tests
268
269      IF ( ln_tst_nemotam ) CALL tsttam
270
271   END SUBROUTINE nemotam_sub
272
273   SUBROUTINE nemotam_final
274      !!----------------------------------------------------------------------
275      !!                    ***  ROUTINE nemotam_final ***
276      !!         
277      !! ** Purpose : Finalize the NEMOTAM run
278      !!
279      !! ** Method  : Close open files
280      !!
281      !! ** Action  : Close open files
282      !!
283      !! History :
284      !!        !  07-06  (K. Mogensen) Original code
285      !!----------------------------------------------------------------------
286
287      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
288
289      IF( nstop /= 0 ) THEN                 ! error print
290         IF(lwp) WRITE(numout,cform_err)
291         IF(lwp) WRITE(numout,*) nstop, ' error have been found' 
292      ENDIF
293
294      IF ( lk_mpp ) CALL mppsync
295
296      ! Deallocate variables
297      ! --------------------
298      CALL oce_tam_deallocate ( 0 )
299      CALL sol_oce_tam_deallocate ( 0 )
300#if defined key_tam
301      CALL sbc_oce_tam_deallocate ( 0 )
302      CALL trc_oce_tam_deallocate ( 0 )
303#endif
304      CALL trj_deallocate
305      ! Unit close
306      ! ----------
307
308      CLOSE( numnam )       ! namelist
309      CLOSE( numout )       ! standard model output file
310      IF (  lini ) THEN
311         CLOSE( numtan_sc )    ! tangent test diagnostic output
312         CLOSE( numtan )       ! tangent diagnostic output
313      ENDIF
314
315      IF ( lk_mpp ) CALL mppstop
316
317   END SUBROUTINE nemotam_final
318
319   SUBROUTINE nemotam_banner(kumout)
320      !!----------------------------------------------------------------------
321      !!                    ***  ROUTINE nemotam_banner ***
322      !!         
323      !! ** Purpose : Print a banner to a unit
324      !!
325      !! ** Method  : Fortran
326      !!
327      !! ** Action  : Fortran
328      !!
329      !! History :
330      !!        !  07-06  (A. Vidard) Original code
331      !!----------------------------------------------------------------------
332      !! * Arguments
333      INTEGER, INTENT(in) :: &
334         & kumout  ! Unit to print the banner to.
335
336      WRITE(kumout,*)
337      WRITE(kumout,*) '                         VODA '
338      WRITE(kumout,*) '             NEMO Tangent and Adjoint Model'
339      WRITE(kumout,*) '                    Version 3.0b  (2010) '
340      WRITE(kumout,*)
341
342   END SUBROUTINE nemotam_banner
343
344   SUBROUTINE nemotam_root
345      !!----------------------------------------------------------------------
346      !!                    ***  ROUTINE nemovar_root ***
347      !!         
348      !! ** Purpose : Choose which init must be done according to test
349      !!
350      !! ** Method  : Fortran
351      !!
352      !! ** Action  : Fortran
353      !!
354      !! History :
355      !!        !  09-07  (F. Vigilant) Original code
356      !!----------------------------------------------------------------------
357      !! * Local declarations
358      NAMELIST/namtst/ ln_tst_nemotam, ln_tst_cpd_tam, ln_tst_stp_tam, &
359         &             ln_tst_tan_cpd, ln_tst_tan, ln_tst_stop
360      CHARACTER (len=*), PARAMETER  ::  namelistname = 'namelist.nemotam'
361      !! * Arguments
362
363      ln_tst_nemotam = .FALSE.
364      ln_tst_cpd_tam = .FALSE.
365      ln_tst_stp_tam = .FALSE.
366      ln_tst_tan_cpd = .FALSE.
367      ln_tst_tan     = .FALSE.
368      ln_tst_stop    = .TRUE.
369
370      CALL ctlopn( numnam, namelistname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   &
371         &           1, numout, .FALSE., 1 )
372
373      REWIND( numnam )
374      READ  ( numnam, namtst )
375
376      IF ( ln_tst_tan ) THEN
377#if defined key_tst_tlm
378         CALL  opa_opatam_ini
379         lini = .FALSE.            ! not standard initialisation
380#else
381         CALL ctl_stop( 'Activate key_tst_tlm for ln_tst_tan=.true.' )
382#endif
383      ELSE
384         CALL nemotam_init
385      END IF
386
387   END SUBROUTINE nemotam_root
388
389END MODULE nemotam
Note: See TracBrowser for help on using the repository browser.