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

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/opatam_tst_init.F90 @ 2587

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

refer to ticket #798

File size: 22.2 KB
Line 
1MODULE opatam_tst_ini
2#if defined key_tam
3#if defined key_tst_tlm
4   !!==============================================================================
5   !!                       ***  MODULE opatam_tst_init   ***
6   !! Initialization of OPA and OPATAM for Tangent Linear and Adjoint modules
7   !!==============================================================================
8
9   !!----------------------------------------------------------------------
10   !!   opa_4_tst_ini    : initialization of the opa model
11   !!   opatam_4_tst_ini : initalization of the opatam model
12   !!   opa_hdr_ini      : initialization of the Header Print out file
13   !!----------------------------------------------------------------------
14   !! History :
15   !!   9.0  !  09-06  (F. Vigilant)  Original code
16   !!                                 Mainframe from opa.F90 (07-07)
17   !!----------------------------------------------------------------------
18   !! * Modules used
19   USE oce             ! dynamics and tracers variables
20   USE cpl_oce         ! ocean-atmosphere-sea ice coupled exchanges
21   USE dom_oce         ! ocean space domain variables
22   USE sbc_oce         ! surface boundary condition: ocean
23   USE trdmod_oce      ! ocean variables trends
24   USE daymod          ! calendar
25   USE in_out_manager  ! I/O manager
26   USE lib_mpp         ! distributed memory computing
27   USE domcfg          ! domain configuration               (dom_cfg routine)
28   USE mppini          ! shared/distributed memory setting (mpp_init routine)
29   USE domain          ! domain initialization             (dom_init routine)
30   USE obc_par         ! open boundary cond. parameters
31   USE obcini          ! open boundary cond. initialization (obc_ini routine)
32   USE bdy_par         ! unstructured open boundary cond. parameters
33   USE bdyini          ! unstructured open boundary cond. initialization (bdy_init routine)
34   USE istate          ! initial state setting          (istate_init routine)
35   USE eosbn2          ! equation of state            (eos bn2 routine)
36   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
37
38   ! ocean physics
39   USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine)
40   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine)
41   USE zdfini
42
43   USE phycst          ! physical constant                  (par_cst routine)
44   USE trdmod          ! momentum/tracers trends       (trd_mod_init routine)
45
46   USE diaptr          ! poleward transports           (dia_ptr_init routine)
47
48#if defined key_oasis3
49   USE cpl_oasis3      ! OASIS3 coupling (to ECHAM5)
50#elif defined key_oasis4
51   USE cpl_oasis4      ! OASIS4 coupling (to ECHAM5)
52#endif
53   USE dynspg_oce      ! Control choice of surface pressure gradient schemes
54   USE prtctl          ! Print control                 (prt_ctl_init routine)
55   USE c1d             ! 1D configuration
56   USE dyncor_c1d      ! Coriolis factor at T-point
57#if defined key_top
58   USE trcini          ! Initialization of the passive tracers
59#endif
60   !! * Modules used for TAM
61   USE domcfg          ! domain configuration               (dom_cfg routine)
62   USE tamctl          ! Control parameters
63   USE tamtrj          ! handling of the trajectory
64   USE oce_tam         ! TL and adjoint data
65   USE sbc_oce_tam     ! Surface BCs tangent and adjoint arrays
66   USE trc_oce_tam     ! Trend tangent and adjoint arrays
67   USE sol_oce_tam     ! Solver tangent and adjoint arrays
68   ! ocean physics
69   USE zdfini 
70   USE opa
71   USE par_tlm
72
73   IMPLICIT NONE
74   PRIVATE
75
76   !! * Module variables
77   CHARACTER (len=64) ::        &
78      cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
79   LOGICAL :: ldirinit = .FALSE.            ! flag if initialization of direct is done
80
81   !! * Routine accessibility
82   PUBLIC &
83     & opa_opatam_ini,          &
84     & opa_4_tst_ini,           &
85     & opatam_4_tst_ini,        &
86     & tlm_namrd
87
88
89CONTAINS
90
91   SUBROUTINE opa_opatam_ini
92      !!----------------------------------------------------------------------
93      !!                     ***  ROUTINE opa_4_tst_ini  ***
94      !!
95      !! ** Purpose :   initialization of the opa+opatam model
96      !!
97      !! History :
98      !!   9.0  !  09-07  (F. Vigilant) 
99      !!                                 
100      !!----------------------------------------------------------------------
101
102      ! Initialization
103      CALL opa_hdr_ini
104      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
105      CALL opa_flg                          ! Control prints & Benchmark
106      CALL tlm_namrd
107
108      SELECT CASE (tlm_bch)
109         CASE ( 0, 1 )
110      CALL  opa_4_tst_ini
111         CASE ( 2 )
112      CALL  opatam_4_tst_ini
113         CASE DEFAULT
114            CALL ctl_stop( '        Wrong Value of tlm_bch')
115      END SELECT
116
117
118   END SUBROUTINE opa_opatam_ini
119
120   SUBROUTINE opa_4_tst_ini
121      !!----------------------------------------------------------------------
122      !!                     ***  ROUTINE opa_4_tst_ini  ***
123      !!
124      !! ** Purpose :   initialization of the opa model
125      !!
126      !! History :
127      !!   9.0  !  09-06  (F. Vigilant)  import from opa_ini
128      !!                                 
129      !!----------------------------------------------------------------------
130 
131#if defined key_coupled
132      INTEGER ::   itro, istp0        ! ???
133#endif
134
135      ! Initializations
136      ! ===============
137
138      !                                     ! ============================== !
139      !                                     !  Model general initialization  !
140      !                                     ! ============================== !
141
142                                            ! Domain decomposition
143      IF( jpni*jpnj == jpnij ) THEN
144         CALL mpp_init                          ! standard cutting out
145      ELSE
146         CALL mpp_init2                         ! eliminate land processors
147      ENDIF
148     
149      CALL phy_cst                          ! Physical constants
150
151      CALL dom_cfg                          ! Domain configuration
152     
153      CALL dom_init                         ! Domain
154
155      IF( lk_c1d    ) THEN                      ! adaptation for 1D configuration
156         CALL cor_c1d                                ! redefine Coriolis at T-point
157         umask(:,:,:) = tmask(:,:,:)                 ! U, V and T-points are the same
158         vmask(:,:,:) = tmask(:,:,:)                 !
159      ENDIF
160
161      IF( ln_ctl    )   CALL prt_ctl_init   ! Print control
162
163      IF( lk_obc    )   CALL obc_init       ! Open boundaries
164
165      IF( lk_bdy    )   CALL bdy_init       ! Unstructured open boundaries
166
167!      CALL istate_init                      ! ocean initial state (Dynamics and tracers)
168!      CALL istate_p
169      !                                     ! Ocean physics
170
171      CALL ldf_dyn_init                         ! Lateral ocean momentum physics
172
173      CALL ldf_tra_init                         ! Lateral ocean tracer physics
174
175      CALL zdf_init                             ! Vertical ocean physics
176
177      CALL trd_mod_init                         ! Mixed-layer/Vorticity/Integral constraints trends
178
179#if defined key_top
180      CALL trc_ini                           ! Passive tracers
181#endif
182
183      IF(lwp) WRITE(numout,*)'Euler time step switch is ', neuler
184      ldirinit = .TRUE.
185
186      CALL     tam_trj_ini
187
188      CALL day_init
189      CALL day(nit000)
190
191      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
192
193   END SUBROUTINE opa_4_tst_ini
194
195   SUBROUTINE opa_hdr_ini
196      !!----------------------------------------------------------------------
197      !!                     ***  ROUTINE opa_hdr_ini  ***
198      !!
199      !! ** Purpose :   initialization of the Header Print out file
200      !!
201      !! History :
202      !!   9.0  !  09-06  (F. Vigilant)  extract from opa_ini
203      !!                                 
204      !!----------------------------------------------------------------------
205
206      ! local declaration
207#if defined key_oasis3 || defined key_oasis4
208      INTEGER :: localComm
209#endif
210      CHARACTER (len=20) ::   namelistname
211      CHARACTER (len=28) ::   file_out
212      NAMELIST/namctl/ ln_ctl, nprint, nictls, nictle,   &
213         &             isplt , jsplt , njctls, njctle, nbench, nbit_cmp
214      ! Initializations
215      ! ===============
216
217      file_out = 'nemotam_tst.output'
218     
219      ! open listing and namelist units
220      CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
221         &         'SEQUENTIAL', 1, 6, .FALSE., 1 )
222
223      WRITE(numout,*)
224      WRITE(numout,*) '                 L O D Y C - I P S L'
225      WRITE(numout,*) '                     O P A model'
226      WRITE(numout,*) '            Ocean General Circulation Model'
227      WRITE(numout,*) '               version OPA 9.0  (2005) '
228      WRITE(numout,*)
229      WRITE(numout,*)
230
231      ! Namelist namctl : Control prints & Benchmark
232      REWIND( numnam )
233      READ  ( numnam, namctl )
234
235#if defined key_oasis3 || defined key_oasis4
236      call cpl_prism_init(localComm)
237      ! Nodes selection
238      narea = mynode(localComm)
239#else
240      ! Nodes selection
241      nproc = mynode()
242      narea = nproc + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
243#endif
244      narea = narea + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
245      lwp   = narea == 1
246
247      ! open additionnal listing
248!      IF( ln_ctl )   THEN
249         IF( narea-1 > 0 )   THEN
250            WRITE(file_out,FMT="('nemotam_tst.output_',I4.4)") narea-1
251            CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
252               &         'SEQUENTIAL', 1, numout, .FALSE., 1 )
253            lwp = .TRUE.
254         ENDIF
255            !
256!      ENDIF
257      IF(lwp) THEN
258            WRITE(numout,*)
259            WRITE(numout,*) '                 L O D Y C - I P S L'
260            WRITE(numout,*) '                     O P A model'
261            WRITE(numout,*) '            Ocean General Circulation Model'
262            WRITE(numout,*) '               version OPA 9.0  (2005) '
263            WRITE(numout,*) '                   MPI Ocean output '
264            WRITE(numout,*)
265            WRITE(numout,*)
266      ENDIF
267
268
269   END SUBROUTINE opa_hdr_ini
270
271   SUBROUTINE opatam_4_tst_ini
272      !!----------------------------------------------------------------------
273      !!                    ***  ROUTINE nemotam_init  ***
274      !!         
275      !! ** Purpose : Initialize grids
276      !!
277      !! ** Method  : Read the namelist and call reading routines
278      !!
279      !! ** Action  : Read the namelist and call reading routines
280      !!
281      !! History :
282      !!        !  09-06  (F. Vigilant) Extract from nemovar_init routine
283      !!----------------------------------------------------------------------
284
285      !! * Local declarations
286      CHARACTER (len=128) :: file_out !!= 'nemovar.output'
287
288
289      ! Nodes selection
290      nproc = mynode()
291      narea = nproc + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
292      lwp   = narea == 1
293
294      ! open additionnal listing
295      IF( narea-1 > 0 )   THEN
296!!         IF ( .NOT. ldirinit) THEN
297!!            WRITE(file_out,FMT="('nemovar.output_',I4.4)") narea-1
298!!            IF( numout /= 0 .AND. numout /= 6 ) THEN
299!!               CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
300!!               &         'SEQUENTIAL', 1, numout, .FALSE., 1 )
301!!            ENDIF
302!         CALL nemotam_banner( numout )
303!!         ENDIF
304         lwp = .TRUE.
305         !
306      ENDIF     
307
308      IF(lwp) THEN
309         WRITE(numout,*)
310         WRITE(numout,*) 'nemotam_init: Control prints & Benchmark'
311         WRITE(numout,*) '~~~~~~~~~~~~ '
312         WRITE(numout,*) '          Namelist namctl'
313         WRITE(numout,*) '             run control (for debugging)     ln_ctl    = ', ln_ctl
314         WRITE(numout,*) '             level of print                  nprint    = ', nprint
315         WRITE(numout,*) '             bit comparison mode (0/1)       nbit_cmp  = ', nbit_cmp
316      ENDIF
317
318      IF ( .NOT. ldirinit ) THEN
319        IF( jpni*jpnj == jpnij ) THEN
320           CALL mpp_init                      ! standard cutting out
321        ELSE
322           CALL mpp_init2                     ! eliminate land processors
323        ENDIF
324      ENDIF
325
326      IF (lwp) THEN
327         ! Diagnostic file for tangent test
328         WRITE(file_out,FMT="('tan_diag.output_',I4.4)") , narea-1
329         CALL ctlopn( numtan, file_out, 'UNKNOWN', 'FORMATTED',   &
330            &         'SEQUENTIAL', 1, numtan, .FALSE., 1 )
331
332         WRITE(numtan,*) 'Routine loop      p      Nn=M(X+dX)-M(X)         En=Nn / L(hdX)       ', &
333              & 'Er = (Nn -L)/L            L                  Nn-L                   (En-1)/p   ', &
334              & '         Er/p'
335         WRITE(numtan,*) ' ---------------------------------------------------------------------',&
336              & '-------------------------------------------------------------------------------',&
337              & '-------------'
338      ENDIF
339
340      IF (lwp) THEN
341         ! Diagnostic file for tangent test (scalar sampling)
342         WRITE(file_out,FMT="('tan_diag_sc.output_',I4.4)") , narea-1
343         CALL ctlopn( numtan_sc, file_out, 'UNKNOWN', 'FORMATTED',   &
344            &         'SEQUENTIAL', 1, numtan_sc, .FALSE., 1 )
345
346         WRITE(numtan_sc,*) 'Routine  scalar    loop    p     index i_pos. ', &
347              & 'j_pos.       scalar value'
348         WRITE(numtan_sc,*) ' ---------------------------------------------',&
349              & '-------------------------'
350      ENDIF
351
352      IF ( .NOT. ldirinit ) THEN
353         CALL phy_cst                          ! Physical constants
354         CALL dom_cfg                          ! Domain configuration 
355         CALL dom_init                         ! Domain
356
357          ! Ocean physics
358#if defined key_tam
359         CALL ldf_dyn_init                         ! Lateral ocean momentum physics
360         CALL ldf_tra_init                         ! Lateral ocean tracer physics
361#endif
362         CALL zdf_init                             ! Vertical ocean physics
363      ENDIF
364       
365      CALL     oce_tam_init( 1 )            ! OCE TAM field
366      IF ( ldirinit ) THEN
367         CALL sol_oce_tam_init( 1 )            ! Initialize solver tangent variables
368      ELSE
369         CALL sol_oce_tam_init( 0 )            ! Initialize solver tangent variables
370      ENDIF
371      CALL trc_oce_tam_init( 1 )            ! TRC TAM fields
372#if defined key_tam
373      CALL sbc_oce_tam_init( 1 )            ! SBC TAM fields
374#endif
375
376      IF ( .NOT. ldirinit) CALL     tam_trj_ini
377
378      CALL day_init
379      IF ( .NOT. ldirinit) CALL day( nit000 )
380
381#ifdef EVENTUALLY
382
383#endif
384      neuler=1
385
386      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
387
388   END SUBROUTINE opatam_4_tst_ini
389
390   SUBROUTINE opa_flg
391      !!----------------------------------------------------------------------
392      !!                     ***  ROUTINE opa  ***
393      !!
394      !! ** Purpose :   Initialize logical flags that control the choice of
395      !!      some algorithm or control print
396      !!
397      !! ** Method  :    Read in namilist namflg logical flags
398      !!
399      !! History :
400      !!   9.0  !  03-11  (G. Madec)  Original code
401      !!----------------------------------------------------------------------
402      !! * Local declarations
403
404      NAMELIST/namflg/ ln_dynhpg_imp, nn_dynhpg_rst
405      !!----------------------------------------------------------------------
406
407      ! Parameter control and print
408      ! ---------------------------
409      IF(lwp) THEN
410         WRITE(numout,*)
411         WRITE(numout,*) 'opa_flg: Control prints & Benchmark'
412         WRITE(numout,*) '~~~~~~~ '
413         WRITE(numout,*) '          Namelist namctl'
414         WRITE(numout,*) '             run control (for debugging)     ln_ctl    = ', ln_ctl
415         WRITE(numout,*) '             level of print                  nprint    = ', nprint
416         WRITE(numout,*) '             Start i indice for SUM control  nictls    = ', nictls
417         WRITE(numout,*) '             End i indice for SUM control    nictle    = ', nictle
418         WRITE(numout,*) '             Start j indice for SUM control  njctls    = ', njctls
419         WRITE(numout,*) '             End j indice for SUM control    njctle    = ', njctle
420         WRITE(numout,*) '             number of proc. following i     isplt     = ', isplt
421         WRITE(numout,*) '             number of proc. following j     jsplt     = ', jsplt
422         WRITE(numout,*) '             benchmark parameter (0/1)       nbench    = ', nbench
423         WRITE(numout,*) '             bit comparison mode (0/1)       nbit_cmp  = ', nbit_cmp
424      ENDIF
425
426      ! ... Control the sub-domain area indices for the control prints
427      IF( ln_ctl )   THEN
428         IF( lk_mpp )   THEN
429            ! the domain is forced to the real splitted domain in MPI
430            isplt = jpni ; jsplt = jpnj ; ijsplt = jpni*jpnj
431         ELSE
432            IF( isplt == 1 .AND. jsplt == 1  ) THEN
433               CALL ctl_warn( '          - isplt & jsplt are equal to 1',   &
434                    &         '          - the print control will be done over the whole domain' )
435            ENDIF
436
437            ! compute the total number of processors ijsplt
438            ijsplt = isplt*jsplt
439         ENDIF
440
441         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
442         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
443
444         ! Control the indices used for the SUM control
445         IF( nictls+nictle+njctls+njctle == 0 )   THEN
446            ! the print control is done over the default area
447            lsp_area = .FALSE.
448         ELSE
449            ! the print control is done over a specific  area
450            lsp_area = .TRUE.
451            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
452               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
453               nictls = 1
454            ENDIF
455
456            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
457               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
458               nictle = jpiglo
459            ENDIF
460
461            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
462               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
463               njctls = 1
464            ENDIF
465
466            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
467               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
468               njctle = jpjglo
469            ENDIF
470
471         ENDIF          ! IF( nictls+nictle+njctls+njctle == 0 )
472       ENDIF            ! IF(ln_ctl)
473
474      IF( nbench == 1 )   THEN
475         SELECT CASE ( cp_cfg )
476         CASE ( 'gyre' )
477            CALL ctl_warn( '          The Benchmark is activated ' )
478         CASE DEFAULT
479            CALL ctl_stop( '          The Benchmark is based on the GYRE configuration: key_gyre must &
480               &                      be used or set nbench = 0' )
481         END SELECT
482      ENDIF
483
484      IF( nbit_cmp == 1 )   THEN
485         CALL ctl_warn( '          Bit comparison enabled. Single and multiple processor results must bit compare', &
486              &         '          WARNING: RESULTS ARE NOT PHYSICAL.' )
487      ENDIF
488
489
490      ! Read Namelist namflg : algorithm FLaG
491      ! --------------------
492      REWIND ( numnam )
493      READ   ( numnam, namflg )
494
495      ! Parameter control and print
496      ! ---------------------------
497      IF(lwp) THEN
498         WRITE(numout,*)
499         WRITE(numout,*) 'opa_flg : Hydrostatic pressure gradient algorithm'
500         WRITE(numout,*) '~~~~~~~'
501         WRITE(numout,*) '          Namelist namflg : set algorithm flags'
502         WRITE(numout,*) '             centered (F) or semi-implicit (T)   ln_dynhpg_imp = ', ln_dynhpg_imp
503         WRITE(numout,*) '             hydrostatic pressure gradient'
504         WRITE(numout,*) '             add dynhpg implicit variable        nn_dynhpg_rst = ', nn_dynhpg_rst
505         WRITE(numout,*) '             in restart ot not nn_dynhpg_rst'
506      ENDIF
507      IF( .NOT. ln_dynhpg_imp )   nn_dynhpg_rst = 0      ! force no adding dynhpg implicit variables in restart
508
509   END SUBROUTINE opa_flg
510
511
512   SUBROUTINE opa_closefile
513      !!----------------------------------------------------------------------
514      !!                     ***  ROUTINE opa_closefile  ***
515      !!
516      !! ** Purpose :   Close the files
517      !!
518      !! ** Method  :
519      !!
520      !! History :
521      !!   9.0  !  05-01  (O. Le Galloudec)  Original code
522      !!----------------------------------------------------------------------
523      !! * Modules used
524      USE dtatem        ! temperature data
525      USE dtasal        ! salinity data
526      !!----------------------------------------------------------------------
527
528      IF ( lk_mpp ) CALL mppsync
529
530      ! 1. Unit close
531      ! -------------
532
533      CLOSE( numnam )           ! namelist
534      CLOSE( numout )           ! standard model output file
535
536      IF(lwp) CLOSE( numstp )   ! time-step file
537      IF(lwp) CLOSE( numsol )
538
539   END SUBROUTINE opa_closefile
540
541   SUBROUTINE tlm_namrd
542      !!----------------------------------------------------------------------
543      !!                     ***  ROUTINE tlm_namrd  ***
544      !!
545      !! ** Purpose :   Control feature of stp_tlm_tst loops
546      !!
547      !! ** Method  :    Read in namilist namtst_tlm parameters
548      !!
549      !! History :
550      !!   9.0  !  09-07  (F. Vigilant)  Original code
551      !!----------------------------------------------------------------------
552      !! * Module used
553      USE in_out_manager, ONLY: & ! I/O manager
554      & numout,                 &
555      & numnam,                 &
556      & lwp
557      !! * Local declarations
558
559      NAMELIST/namtst_tlm/ tlm_bch, cur_loop, h_ratio
560
561      ! Read Namelist namflg : algorithm FLaG
562      ! --------------------
563      REWIND ( numnam )
564      READ   ( numnam, namtst_tlm )
565
566      ! Parameter control and print
567      ! ---------------------------
568      IF(lwp) THEN
569         WRITE(numout,*)
570         WRITE(numout,*) 'tlm_namrd : Current loop iteration and h_ratio values '
571         WRITE(numout,*) '~~~~~~~~~'
572         WRITE(numout,*) '          Namelist namtst_tlm : set algorithm parameters'
573         WRITE(numout,*) '             current branch test     = ' , tlm_bch
574         WRITE(numout,*) '             current loop iteration  = ' , cur_loop
575         WRITE(numout,*) '             current h_ratio applied = ' , h_ratio
576         WRITE(numout,*) 
577      ENDIF
578
579   END SUBROUTINE tlm_namrd
580
581   !!======================================================================
582#endif
583#endif
584END MODULE opatam_tst_ini
Note: See TracBrowser for help on using the repository browser.