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

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

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

refer to ticket #798

File size: 17.8 KB
Line 
1MODULE opahlt
2#if defined key_tam
3   !!==============================================================================
4   !!                       ***  MODULE opa_htl   ***
5   !! Ocean system   : OPA ocean dynamics (including on-line tracers and sea-ice)
6   !!==============================================================================
7
8   !!----------------------------------------------------------------------
9   !!   opa_hlt            : solve ocean dynamics, tracer and/or sea-ice
10   !!   opa_htl_init       : initialization of the opa model
11   !!   opa_hlt_closefile  : close remaining files
12   !!----------------------------------------------------------------------
13   !! History :
14   !!                  ()  Original code from opa
15   !!        !  10-07  (F. Vigilant) Modification for tangent linear hyp
16   !!----------------------------------------------------------------------
17   !! * Modules used
18   USE oce             ! dynamics and tracers variables
19   USE dom_oce         ! ocean space domain variables
20   USE sbc_oce         ! surface boundary condition: ocean
21   USE trdmod_oce      ! ocean variables trends
22   USE daymod          ! calendar
23   USE in_out_manager  ! I/O manager
24   USE lib_mpp         ! distributed memory computing
25
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 diaobs          ! Observation diagnostics       (dia_obs_init routine)
46
47   USE asminc          ! assimilation increments       (asm_inc_init routine)
48!   USE asmbkg          ! writing out background state   
49   USE tamtrj          ! writing out state trajectory
50!   USE bias            ! bias (T,S,SSH)                   (bias_init routine)
51!   USE biaspar         ! bias  parameters
52
53   USE step            ! OPA time-stepping                  (stp     routine)
54   USE dynspg_oce      ! Control choice of surface pressure gradient schemes
55   USE prtctl          ! Print control                 (prt_ctl_init routine)
56   USE c1d             ! 1D configuration
57   USE dyncor_c1d      ! Coriolis factor at T-point
58!   USE step_c1d        ! Time stepping loop for the 1D configuration
59
60   USE trcini          ! Initialization of the passive tracers
61   USE par_tlm
62
63   USE hltinc, ONLY : &
64     & hlt_inc_bld
65
66   IMPLICIT NONE
67   PRIVATE
68
69   !! * Module variables
70   CHARACTER (len=64) ::        &
71      cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
72
73   !! * Routine accessibility
74   PUBLIC opa_hlt        ! called by hlttst.F90
75
76CONTAINS
77
78   SUBROUTINE opa_hlt
79      !!----------------------------------------------------------------------
80      !!                     ***  ROUTINE opa_hlt  ***
81      !!
82      !! ** Purpose :   opa_hlt solves the primitive equations on an orthogonal
83      !!      curvilinear mesh on the sphere.
84      !!
85      !! ** Method  : - model general initialization
86      !!              - launch the time-stepping (stp routine)
87      !!
88      !! References :
89      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
90      !!              internal report, IPSL.
91      !!----------------------------------------------------------------------
92      INTEGER ::   istp       ! time step index
93      !!----------------------------------------------------------------------
94
95#if defined key_agrif
96      CALL ctl_stop( '       Agrif not available')
97#endif
98     
99      CALL opa_hlt_init  ! Initializations
100
101      ! check that all process are still there... If some process have an error,
102      ! they will never enter in step and other processes will wait until the end of the cpu time!
103      IF( lk_mpp )   CALL mpp_max( nstop )
104
105      istp = nit000
106      IF( lk_c1d ) THEN                 ! 1D configuration (no AGRIF zoom)
107         CALL ctl_stop( '       lk_c1d not available')
108      ELSE
109
110         istp = nit000 - 1               
111         IF( (nstg == 1) .OR. (nstg == 3) ) CALL hlt_inc_bld( nstg )      ! increment builder
112
113
114IF( nstg .NE. 3 ) THEN
115         istp = nit000
116PRINT*,'STARTING LOOP STP'
117         DO WHILE ( istp <= nitend .AND. nstop == 0 )
118#if defined key_agrif
119            CALL ctl_stop( '       Agrif not available')
120#else
121            CALL stp( istp )
122#endif
123            istp = istp + 1
124            IF( lk_mpp )   CALL mpp_max( nstop )
125         END DO
126ENDIF
127      ENDIF
128
129      !                                     ! ========= !
130      !                                     !  Job end  !
131      !                                     ! ========= !
132
133      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
134
135      IF( nstop /= 0 .AND. lwp ) THEN                 ! error print
136         WRITE(numout,cform_err)
137         WRITE(numout,*) nstop, ' error have been found' 
138      ENDIF
139
140      CALL opa_hlt_closefile
141
142      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp)
143      !
144   END SUBROUTINE opa_hlt
145
146   SUBROUTINE opa_hlt_init
147      !!----------------------------------------------------------------------
148      !!                     ***  ROUTINE opa_init  ***
149      !!
150      !! ** Purpose :   initialization of the opa model
151      !!
152      !!----------------------------------------------------------------------
153#if defined key_coupled
154      INTEGER ::   itro, istp0        ! ???
155#endif
156#if defined key_oasis3 || defined key_oasis4
157      INTEGER :: localComm
158#endif
159!      CHARACTER (len=20) ::   namelistname
160      CHARACTER (len=28) ::   file_out
161      NAMELIST/namctl/ ln_ctl, nprint, nictls, nictle,   &
162         &             isplt , jsplt , njctls, njctle, nbench, nbit_cmp
163      !!----------------------------------------------------------------------
164
165      ! Initializations
166      ! ===============
167
168      file_out = 'nemohlt.output'
169
170      ! Namelist namctl : Control prints & Benchmark
171      REWIND( numnam )
172      READ  ( numnam, namctl )
173
174#if defined key_oasis3 || defined key_oasis4
175      CALL ctl_stop( '       Key_oasis3 and key_oasis4 not available')
176#else
177      ! Nodes selection
178      nproc = mynode()
179#endif
180      narea = nproc + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
181      lwp   = narea == 1
182
183      ! open additionnal listing
184      IF( ln_ctl )   THEN
185         IF( narea-1 > 0 )   THEN
186            WRITE(file_out,FMT="('nemohlt.output_',I4.4)") narea-1
187            CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
188               &         'SEQUENTIAL', 1, numout, .FALSE., 1 )
189            lwp = .TRUE.
190            !
191            WRITE(numout,*)
192            WRITE(numout,*) '                 L O D Y C - I P S L'
193            WRITE(numout,*) '                     O P A model'
194            WRITE(numout,*) '            Ocean General Circulation Model'
195            WRITE(numout,*) '               version OPA 9.0  (2005) '
196            WRITE(numout,*) '                   MPI Ocean output '
197            WRITE(numout,*)
198            WRITE(numout,*)
199         ENDIF
200      ENDIF
201
202      ! Parameter control and print
203      ! ---------------------------
204      IF(lwp) THEN
205         WRITE(numout,*)
206         WRITE(numout,*) '              LINEAR-TANGENT HYPOTHESIS TEST-RUN '
207         WRITE(numout,*) '              ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
208         WRITE(numout,*) '       Namelist namhlt'
209         WRITE(numout,*) '             run stage                        nstg       = ', nstg
210         IF( nstg == 1 ) THEN
211            WRITE(numout,*) '             temperature increment switch     ln_hltt    = ', ln_hltt
212            WRITE(numout,*) '             salinity increment switch        ln_hlts    = ', ln_hlts
213            WRITE(numout,*) '             velocity incr. switch            ln_hltuv   = ', ln_hltuv
214            WRITE(numout,*) '             sea surface height incr. switch  ln_hltssh  = ', ln_hltssh
215         ENDIF
216         WRITE(numout,*)
217         WRITE(numout,*)
218      ENDIF
219
220
221      !                                     ! ============================== !
222      !                                     !  Model general initialization  !
223      !                                     ! ============================== !
224
225      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
226
227      CALL opa_hlt_flg                          ! Control prints & Benchmark
228
229                                            ! Domain decomposition
230      IF( jpni*jpnj == jpnij ) THEN
231         CALL mpp_init                          ! standard cutting out
232      ELSE
233         CALL mpp_init2                         ! eliminate land processors
234      ENDIF
235     
236      CALL phy_cst                          ! Physical constants
237
238      CALL dom_cfg                          ! Domain configuration
239     
240      CALL dom_init                         ! Domain
241
242      IF( lk_c1d    ) THEN                      ! adaptation for 1D configuration
243         CALL cor_c1d                                ! redefine Coriolis at T-point
244         umask(:,:,:) = tmask(:,:,:)                 ! U, V and T-points are the same
245         vmask(:,:,:) = tmask(:,:,:)                 !
246      ENDIF
247
248      IF( ln_ctl    )   CALL prt_ctl_init   ! Print control
249
250      IF( lk_obc    )   CALL obc_init       ! Open boundaries
251
252      IF( lk_bdy    )   CALL bdy_init       ! Unstructured open boundaries
253
254      CALL istate_init                      ! ocean initial state (Dynamics and tracers)
255
256      !                                     ! Ocean physics
257
258      CALL ldf_dyn_init                         ! Lateral ocean momentum physics
259
260      CALL ldf_tra_init                         ! Lateral ocean tracer physics
261
262      CALL zdf_init                             ! Vertical ocean physics
263
264      CALL trd_mod_init                         ! Mixed-layer/Vorticity/Integral constraints trends
265
266
267#if defined key_top
268      CALL ctl_stop( '       Key_top not available')
269#endif
270
271#if defined key_coupled && ! defined key_oasis3 && ! defined key_oasis4
272      CALL ctl_stop( '       Key_coupled not available')
273#endif
274
275#if defined key_oasis3 || defined key_oasis4
276      CALL ctl_stop( '       Key_oasis3 and key_oasis4 not available')
277#endif
278!      IF( lk_diaobs ) THEN
279!         CALL dia_obs_init                  ! Initialize observational data
280!         CALL dia_obs( nit000 - 1 )         ! Observation operator for restart
281!      ENDIF
282
283!      CALL dia_ptr_init                     ! Poleward TRansports initialization
284      IF( lk_asminc ) CALL asm_inc_init     ! Initialize assimilation increments
285      CALL tam_trj_ini
286      IF(lwp) WRITE(numout,*)'Euler time step switch is ', neuler
287
288!      CALL bias_init                        ! Initialize bias options
289      !                                     ! =============== !
290      !                                     !  time stepping  !
291      !                                     ! =============== !
292
293      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
294
295   END SUBROUTINE opa_hlt_init
296
297
298   SUBROUTINE opa_hlt_flg
299      !!----------------------------------------------------------------------
300      !!                     ***  ROUTINE opa  ***
301      !!
302      !! ** Purpose :   Initialize logical flags that control the choice of
303      !!      some algorithm or control print
304      !!
305      !! ** Method  :    Read in namilist namflg logical flags
306      !!
307      !! History :
308      !!   9.0  !  03-11  (G. Madec)  Original code
309      !!----------------------------------------------------------------------
310      !! * Local declarations
311
312      NAMELIST/namflg/ ln_dynhpg_imp, nn_dynhpg_rst
313      !!----------------------------------------------------------------------
314
315      ! Parameter control and print
316      ! ---------------------------
317      IF(lwp) THEN
318         WRITE(numout,*)
319         WRITE(numout,*) 'opa_flg: Control prints & Benchmark'
320         WRITE(numout,*) '~~~~~~~ '
321         WRITE(numout,*) '          Namelist namctl'
322         WRITE(numout,*) '             run control (for debugging)     ln_ctl    = ', ln_ctl
323         WRITE(numout,*) '             level of print                  nprint    = ', nprint
324         WRITE(numout,*) '             Start i indice for SUM control  nictls    = ', nictls
325         WRITE(numout,*) '             End i indice for SUM control    nictle    = ', nictle
326         WRITE(numout,*) '             Start j indice for SUM control  njctls    = ', njctls
327         WRITE(numout,*) '             End j indice for SUM control    njctle    = ', njctle
328         WRITE(numout,*) '             number of proc. following i     isplt     = ', isplt
329         WRITE(numout,*) '             number of proc. following j     jsplt     = ', jsplt
330         WRITE(numout,*) '             benchmark parameter (0/1)       nbench    = ', nbench
331         WRITE(numout,*) '             bit comparison mode (0/1)       nbit_cmp  = ', nbit_cmp
332      ENDIF
333
334      ! ... Control the sub-domain area indices for the control prints
335      IF( ln_ctl )   THEN
336         IF( lk_mpp )   THEN
337            ! the domain is forced to the real splitted domain in MPI
338            isplt = jpni ; jsplt = jpnj ; ijsplt = jpni*jpnj
339         ELSE
340            IF( isplt == 1 .AND. jsplt == 1  ) THEN
341               CALL ctl_warn( '          - isplt & jsplt are equal to 1',   &
342                    &         '          - the print control will be done over the whole domain' )
343            ENDIF
344
345            ! compute the total number of processors ijsplt
346            ijsplt = isplt*jsplt
347         ENDIF
348
349         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
350         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
351
352         ! Control the indices used for the SUM control
353         IF( nictls+nictle+njctls+njctle == 0 )   THEN
354            ! the print control is done over the default area
355            lsp_area = .FALSE.
356         ELSE
357            ! the print control is done over a specific  area
358            lsp_area = .TRUE.
359            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
360               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
361               nictls = 1
362            ENDIF
363
364            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
365               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
366               nictle = jpiglo
367            ENDIF
368
369            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
370               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
371               njctls = 1
372            ENDIF
373
374            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
375               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
376               njctle = jpjglo
377            ENDIF
378
379         ENDIF          ! IF( nictls+nictle+njctls+njctle == 0 )
380       ENDIF            ! IF(ln_ctl)
381
382      IF( nbench == 1 )   THEN
383         SELECT CASE ( cp_cfg )
384         CASE ( 'gyre' )
385            CALL ctl_warn( '          The Benchmark is activated ' )
386         CASE DEFAULT
387            CALL ctl_stop( '          The Benchmark is based on the GYRE configuration: key_gyre must &
388               &                      be used or set nbench = 0' )
389         END SELECT
390      ENDIF
391
392      IF( nbit_cmp == 1 )   THEN
393         CALL ctl_warn( '          Bit comparison enabled. Single and multiple processor results must bit compare', &
394              &         '          WARNING: RESULTS ARE NOT PHYSICAL.' )
395      ENDIF
396
397
398      ! Read Namelist namflg : algorithm FLaG
399      ! --------------------
400      REWIND ( numnam )
401      READ   ( numnam, namflg )
402
403      ! Parameter control and print
404      ! ---------------------------
405      IF(lwp) THEN
406         WRITE(numout,*)
407         WRITE(numout,*) 'opa_flg : Hydrostatic pressure gradient algorithm'
408         WRITE(numout,*) '~~~~~~~'
409         WRITE(numout,*) '          Namelist namflg : set algorithm flags'
410         WRITE(numout,*) '             centered (F) or semi-implicit (T)   ln_dynhpg_imp = ', ln_dynhpg_imp
411         WRITE(numout,*) '             hydrostatic pressure gradient'
412         WRITE(numout,*) '             add dynhpg implicit variable        nn_dynhpg_rst = ', nn_dynhpg_rst
413         WRITE(numout,*) '             in restart ot not nn_dynhpg_rst'
414      ENDIF
415      IF( .NOT. ln_dynhpg_imp )   nn_dynhpg_rst = 0      ! force no adding dynhpg implicit variables in restart
416
417   END SUBROUTINE opa_hlt_flg
418
419
420   SUBROUTINE opa_hlt_closefile
421      !!----------------------------------------------------------------------
422      !!                     ***  ROUTINE opa_closefile  ***
423      !!
424      !! ** Purpose :   Close the files
425      !!
426      !! ** Method  :
427      !!
428      !! History :
429      !!   9.0  !  05-01  (O. Le Galloudec)  Original code
430      !!----------------------------------------------------------------------
431      !! * Modules used
432      !!----------------------------------------------------------------------
433
434      IF ( lk_mpp ) CALL mppsync
435
436      ! 1. Unit close
437      ! -------------
438
439      CLOSE( numnam )           ! namelist
440      CLOSE( numout )           ! standard model output file
441
442      IF(lwp) CLOSE( numstp )   ! time-step file
443      IF(lwp) CLOSE( numsol )
444
445   END SUBROUTINE opa_hlt_closefile
446
447   !!======================================================================
448#endif
449END MODULE opahlt
Note: See TracBrowser for help on using the repository browser.