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

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/opatam_tst_ini.F90 @ 1885

Last change on this file since 1885 was 1885, checked in by rblod, 14 years ago

add TAM sources

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