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.
opa.F90 in branches/TAM_V3_0/NEMO/OPA_SRC – NEMO

source: branches/TAM_V3_0/NEMO/OPA_SRC/opa.F90 @ 1884

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

Light adaptation of NEMO direct model routine to handle TAM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 18.9 KB
Line 
1MODULE opa
2   !!==============================================================================
3   !!                       ***  MODULE opa   ***
4   !! Ocean system   : OPA ocean dynamics (including on-line tracers and sea-ice)
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   opa_model      : solve ocean dynamics, tracer and/or sea-ice
9   !!   opa_init       : initialization of the opa model
10   !!   opa_flg        : initialisation of algorithm flag
11   !!   opa_closefile  : close remaining files
12   !!----------------------------------------------------------------------
13   !! History :
14   !!   4.0  !  90-10  (C. Levy, G. Madec)  Original code
15   !!   7.0  !  91-11  (M. Imbard, C. Levy, G. Madec)
16   !!   7.1  !  93-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
17   !!                   M. Guyon, A. Lazar, P. Delecluse, C. Perigaud,
18   !!                   G. Caniaux, B. Colot, C. Maes ) release 7.1
19   !!        !  92-06  (L.Terray) coupling implementation
20   !!        !  93-11  (M.A. Filiberti) IGLOO sea-ice
21   !!   8.0  !  96-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
22   !!                   M. Guyon, A. Lazar, P. Delecluse, L.Terray,
23   !!                   M.A. Filiberti, J. Vialar, A.M. Treguier,
24   !!                   M. Levy)  release 8.0
25   !!   8.1  !  97-06  (M. Imbard, G. Madec)
26   !!   8.2  !  99-11  (M. Imbard, H. Goosse)  LIM sea-ice model
27   !!        !  99-12  (V. Thierry, A-M. Treguier, M. Imbard, M-A. Foujols)  OPEN-MP
28   !!        !  00-07  (J-M Molines, M. Imbard)  Open Boundary Conditions  (CLIPPER)
29   !!   9.0  !  02-08  (G. Madec)  F90: Free form and modules
30   !!    "   !  04-06  (R. Redler, NEC CCRLE, Germany) add OASIS[3/4] coupled interfaces
31   !!    "   !  04-08  (C. Talandier) New trends organization
32   !!    "   !  05-06  (C. Ethe) Add the 1D configuration possibility
33   !!    "   !  05-11  (V. Garnier) Surface pressure gradient organization
34   !!    "   !  06-03  (L. Debreu, C. Mazauric)  Agrif implementation
35   !!    "   !  06-04  (G. Madec, R. Benshila)  Step reorganization
36   !!    "   !  07-07  (J. Chanut, A. Sellar) Unstructured open boundaries (BDY)
37   !!----------------------------------------------------------------------
38   !! * Modules used
39   USE oce             ! dynamics and tracers variables
40   USE cpl_oce         ! ocean-atmosphere-sea ice coupled exchanges
41   USE dom_oce         ! ocean space domain variables
42   USE sbc_oce         ! surface boundary condition: ocean
43   USE trdmod_oce      ! ocean variables trends
44   USE daymod          ! calendar
45   USE in_out_manager  ! I/O manager
46   USE lib_mpp         ! distributed memory computing
47
48   USE domcfg          ! domain configuration               (dom_cfg routine)
49   USE mppini          ! shared/distributed memory setting (mpp_init routine)
50   USE domain          ! domain initialization             (dom_init routine)
51   USE obc_par         ! open boundary cond. parameters
52   USE obcini          ! open boundary cond. initialization (obc_ini routine)
53   USE bdy_par         ! unstructured open boundary cond. parameters
54   USE bdyini          ! unstructured open boundary cond. initialization (bdy_init routine)
55   USE istate          ! initial state setting          (istate_init routine)
56   USE eosbn2          ! equation of state            (eos bn2 routine)
57   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
58
59   ! ocean physics
60   USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine)
61   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine)
62   USE zdfini
63
64   USE phycst          ! physical constant                  (par_cst routine)
65   USE trdmod          ! momentum/tracers trends       (trd_mod_init routine)
66
67   USE diaptr          ! poleward transports           (dia_ptr_init routine)
68
69   USE tamtrj          ! writing out state trajectory
70
71   USE step            ! OPA time-stepping                  (stp     routine)
72#if defined key_oasis3
73   USE cpl_oasis3      ! OASIS3 coupling (to ECHAM5)
74#elif defined key_oasis4
75   USE cpl_oasis4      ! OASIS4 coupling (to ECHAM5)
76#endif
77   USE dynspg_oce      ! Control choice of surface pressure gradient schemes
78   USE prtctl          ! Print control                 (prt_ctl_init routine)
79   USE c1d             ! 1D configuration
80   USE dyncor_c1d      ! Coriolis factor at T-point
81   USE step_c1d        ! Time stepping loop for the 1D configuration
82
83   USE trcini          ! Initialization of the passive tracers
84
85   IMPLICIT NONE
86   PRIVATE
87
88   !! * Module variables
89   CHARACTER (len=64) ::        &
90      cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
91
92   !! * Routine accessibility
93   PUBLIC opa_model      ! called by model.F90
94   PUBLIC opa_init
95   !!----------------------------------------------------------------------
96   !!  OPA 9.0 , LOCEAN-IPSL (2005)
97   !! $Id$
98   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
99   !!----------------------------------------------------------------------
100
101CONTAINS
102
103   SUBROUTINE opa_model
104      !!----------------------------------------------------------------------
105      !!                     ***  ROUTINE opa  ***
106      !!
107      !! ** Purpose :   opa solves the primitive equations on an orthogonal
108      !!      curvilinear mesh on the sphere.
109      !!
110      !! ** Method  : - model general initialization
111      !!              - launch the time-stepping (stp routine)
112      !!
113      !! References :
114      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
115      !!              internal report, IPSL.
116      !!----------------------------------------------------------------------
117      INTEGER ::   istp       ! time step index
118      !!----------------------------------------------------------------------
119
120#if defined key_agrif
121      CALL Agrif_Init_Grids()
122#endif
123     
124      CALL opa_init  ! Initializations
125
126      ! check that all process are still there... If some process have an error,
127      ! they will never enter in step and other processes will wait until the end of the cpu time!
128      IF( lk_mpp )   CALL mpp_max( nstop )
129
130      istp = nit000
131      IF( lk_c1d ) THEN                 ! 1D configuration (no AGRIF zoom)
132         !
133         DO WHILE ( istp <= nitend .AND. nstop == 0 )
134            CALL stp_c1d( istp )
135            istp = istp + 1
136         END DO
137      ELSE                              ! 3D ocean with or without AGRIF zoom
138         !
139         DO WHILE ( istp <= nitend .AND. nstop == 0 )
140#if defined key_agrif
141            CALL Agrif_Step( stp )
142#else
143            CALL stp( istp )
144#endif
145            istp = istp + 1
146            IF( lk_mpp )   CALL mpp_max( nstop )
147         END DO
148      ENDIF
149      !                                     ! ========= !
150      !                                     !  Job end  !
151      !                                     ! ========= !
152
153      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
154
155      IF( nstop /= 0 .AND. lwp ) THEN                 ! error print
156         WRITE(numout,cform_err)
157         WRITE(numout,*) nstop, ' error have been found' 
158      ENDIF
159
160      CALL opa_closefile
161#if defined key_oasis3 || defined key_oasis4
162      call cpl_prism_finalize
163#else
164      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp)
165#endif
166      !
167   END SUBROUTINE opa_model
168
169
170   SUBROUTINE opa_init
171      !!----------------------------------------------------------------------
172      !!                     ***  ROUTINE opa_init  ***
173      !!
174      !! ** Purpose :   initialization of the opa model
175      !!
176      !!----------------------------------------------------------------------
177#if defined key_coupled
178      INTEGER ::   itro, istp0        ! ???
179#endif
180#if defined key_oasis3 || defined key_oasis4
181      INTEGER :: localComm
182#endif
183      CHARACTER (len=20) ::   namelistname
184      CHARACTER (len=28) ::   file_out
185      NAMELIST/namctl/ ln_ctl, nprint, nictls, nictle,   &
186         &             isplt , jsplt , njctls, njctle, nbench, nbit_cmp
187      !!----------------------------------------------------------------------
188
189      ! Initializations
190      ! ===============
191
192      file_out = 'ocean.output'
193     
194      ! open listing and namelist units
195      CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
196         &         'SEQUENTIAL', 1, 6, .FALSE., 1 )
197
198      WRITE(numout,*)
199      WRITE(numout,*) '                 L O D Y C - I P S L'
200      WRITE(numout,*) '                     O P A model'
201      WRITE(numout,*) '            Ocean General Circulation Model'
202      WRITE(numout,*) '               version OPA 9.0  (2005) '
203      WRITE(numout,*)
204      WRITE(numout,*)
205
206      namelistname = 'namelist'
207      CALL ctlopn( numnam, namelistname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   &
208         &         1, numout, .FALSE., 1 )
209
210      ! Namelist namctl : Control prints & Benchmark
211      REWIND( numnam )
212      READ  ( numnam, namctl )
213
214#if defined key_oasis3 || defined key_oasis4
215      call cpl_prism_init(localComm)
216      ! Nodes selection
217      narea = mynode(localComm)
218#else
219      ! Nodes selection
220      narea = mynode()
221#endif
222      narea = narea + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
223      lwp   = narea == 1
224
225      ! open additionnal listing
226      IF( ln_ctl )   THEN
227         IF( narea-1 > 0 )   THEN
228            WRITE(file_out,FMT="('ocean.output_',I4.4)") narea-1
229            CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
230               &         'SEQUENTIAL', 1, numout, .FALSE., 1 )
231            lwp = .TRUE.
232            !
233            WRITE(numout,*)
234            WRITE(numout,*) '                 L O D Y C - I P S L'
235            WRITE(numout,*) '                     O P A model'
236            WRITE(numout,*) '            Ocean General Circulation Model'
237            WRITE(numout,*) '               version OPA 9.0  (2005) '
238            WRITE(numout,*) '                   MPI Ocean output '
239            WRITE(numout,*)
240            WRITE(numout,*)
241         ENDIF
242      ENDIF
243
244      !                                     ! ============================== !
245      !                                     !  Model general initialization  !
246      !                                     ! ============================== !
247
248      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
249
250      CALL opa_flg                          ! Control prints & Benchmark
251
252                                            ! Domain decomposition
253      IF( jpni*jpnj == jpnij ) THEN
254         CALL mpp_init                          ! standard cutting out
255      ELSE
256         CALL mpp_init2                         ! eliminate land processors
257      ENDIF
258     
259      CALL phy_cst                          ! Physical constants
260
261      CALL dom_cfg                          ! Domain configuration
262     
263      CALL dom_init                         ! Domain
264
265      IF( lk_c1d    ) THEN                      ! adaptation for 1D configuration
266         CALL cor_c1d                                ! redefine Coriolis at T-point
267         umask(:,:,:) = tmask(:,:,:)                 ! U, V and T-points are the same
268         vmask(:,:,:) = tmask(:,:,:)                 !
269      ENDIF
270
271      IF( ln_ctl    )   CALL prt_ctl_init   ! Print control
272
273      IF( lk_obc    )   CALL obc_init       ! Open boundaries
274
275      IF( lk_bdy    )   CALL bdy_init       ! Unstructured open boundaries
276
277      CALL istate_init                      ! ocean initial state (Dynamics and tracers)
278
279      !                                     ! Ocean physics
280
281      CALL ldf_dyn_init                         ! Lateral ocean momentum physics
282
283      CALL ldf_tra_init                         ! Lateral ocean tracer physics
284
285      CALL zdf_init                             ! Vertical ocean physics
286
287      CALL trd_mod_init                         ! Mixed-layer/Vorticity/Integral constraints trends
288
289
290#if defined key_top
291      CALL trc_ini                           ! Passive tracers
292#endif
293
294#if defined key_coupled && ! defined key_oasis3 && ! defined key_oasis4
295      itro  = nitend - nit000 + 1           ! Coupled
296      istp0 = NINT( rdt )
297      CALL cpl_init( itro, nexco, istp0 )   ! Signal processing and process id exchange
298#endif
299
300#if defined key_oasis3 || defined key_oasis4
301      CALL cpl_prism_define
302#endif
303
304      CALL dia_ptr_init                     ! Poleward TRansports initialization
305
306      CALL tam_trj_ini
307      IF(lwp) WRITE(numout,*)'Euler time step switch is ', neuler
308      !                                     ! =============== !
309      !                                     !  time stepping  !
310      !                                     ! =============== !
311
312      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
313
314   END SUBROUTINE opa_init
315
316
317   SUBROUTINE opa_flg
318      !!----------------------------------------------------------------------
319      !!                     ***  ROUTINE opa  ***
320      !!
321      !! ** Purpose :   Initialize logical flags that control the choice of
322      !!      some algorithm or control print
323      !!
324      !! ** Method  :    Read in namilist namflg logical flags
325      !!
326      !! History :
327      !!   9.0  !  03-11  (G. Madec)  Original code
328      !!----------------------------------------------------------------------
329      !! * Local declarations
330
331      NAMELIST/namflg/ ln_dynhpg_imp, nn_dynhpg_rst
332      !!----------------------------------------------------------------------
333
334      ! Parameter control and print
335      ! ---------------------------
336      IF(lwp) THEN
337         WRITE(numout,*)
338         WRITE(numout,*) 'opa_flg: Control prints & Benchmark'
339         WRITE(numout,*) '~~~~~~~ '
340         WRITE(numout,*) '          Namelist namctl'
341         WRITE(numout,*) '             run control (for debugging)     ln_ctl    = ', ln_ctl
342         WRITE(numout,*) '             level of print                  nprint    = ', nprint
343         WRITE(numout,*) '             Start i indice for SUM control  nictls    = ', nictls
344         WRITE(numout,*) '             End i indice for SUM control    nictle    = ', nictle
345         WRITE(numout,*) '             Start j indice for SUM control  njctls    = ', njctls
346         WRITE(numout,*) '             End j indice for SUM control    njctle    = ', njctle
347         WRITE(numout,*) '             number of proc. following i     isplt     = ', isplt
348         WRITE(numout,*) '             number of proc. following j     jsplt     = ', jsplt
349         WRITE(numout,*) '             benchmark parameter (0/1)       nbench    = ', nbench
350         WRITE(numout,*) '             bit comparison mode (0/1)       nbit_cmp  = ', nbit_cmp
351      ENDIF
352
353      ! ... Control the sub-domain area indices for the control prints
354      IF( ln_ctl )   THEN
355         IF( lk_mpp )   THEN
356            ! the domain is forced to the real splitted domain in MPI
357            isplt = jpni ; jsplt = jpnj ; ijsplt = jpni*jpnj
358         ELSE
359            IF( isplt == 1 .AND. jsplt == 1  ) THEN
360               CALL ctl_warn( '          - isplt & jsplt are equal to 1',   &
361                    &         '          - the print control will be done over the whole domain' )
362            ENDIF
363
364            ! compute the total number of processors ijsplt
365            ijsplt = isplt*jsplt
366         ENDIF
367
368         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
369         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
370
371         ! Control the indices used for the SUM control
372         IF( nictls+nictle+njctls+njctle == 0 )   THEN
373            ! the print control is done over the default area
374            lsp_area = .FALSE.
375         ELSE
376            ! the print control is done over a specific  area
377            lsp_area = .TRUE.
378            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
379               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
380               nictls = 1
381            ENDIF
382
383            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
384               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
385               nictle = jpiglo
386            ENDIF
387
388            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
389               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
390               njctls = 1
391            ENDIF
392
393            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
394               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
395               njctle = jpjglo
396            ENDIF
397
398         ENDIF          ! IF( nictls+nictle+njctls+njctle == 0 )
399       ENDIF            ! IF(ln_ctl)
400
401      IF( nbench == 1 )   THEN
402         SELECT CASE ( cp_cfg )
403         CASE ( 'gyre' )
404            CALL ctl_warn( '          The Benchmark is activated ' )
405         CASE DEFAULT
406            CALL ctl_stop( '          The Benchmark is based on the GYRE configuration: key_gyre must &
407               &                      be used or set nbench = 0' )
408         END SELECT
409      ENDIF
410
411      IF( nbit_cmp == 1 )   THEN
412         CALL ctl_warn( '          Bit comparison enabled. Single and multiple processor results must bit compare', &
413              &         '          WARNING: RESULTS ARE NOT PHYSICAL.' )
414      ENDIF
415
416
417      ! Read Namelist namflg : algorithm FLaG
418      ! --------------------
419      REWIND ( numnam )
420      READ   ( numnam, namflg )
421
422      ! Parameter control and print
423      ! ---------------------------
424      IF(lwp) THEN
425         WRITE(numout,*)
426         WRITE(numout,*) 'opa_flg : Hydrostatic pressure gradient algorithm'
427         WRITE(numout,*) '~~~~~~~'
428         WRITE(numout,*) '          Namelist namflg : set algorithm flags'
429         WRITE(numout,*) '             centered (F) or semi-implicit (T)   ln_dynhpg_imp = ', ln_dynhpg_imp
430         WRITE(numout,*) '             hydrostatic pressure gradient'
431         WRITE(numout,*) '             add dynhpg implicit variable        nn_dynhpg_rst = ', nn_dynhpg_rst
432         WRITE(numout,*) '             in restart ot not nn_dynhpg_rst'
433      ENDIF
434      IF( .NOT. ln_dynhpg_imp )   nn_dynhpg_rst = 0      ! force no adding dynhpg implicit variables in restart
435
436   END SUBROUTINE opa_flg
437
438
439   SUBROUTINE opa_closefile
440      !!----------------------------------------------------------------------
441      !!                     ***  ROUTINE opa_closefile  ***
442      !!
443      !! ** Purpose :   Close the files
444      !!
445      !! ** Method  :
446      !!
447      !! History :
448      !!   9.0  !  05-01  (O. Le Galloudec)  Original code
449      !!----------------------------------------------------------------------
450      !! * Modules used
451      USE dtatem        ! temperature data
452      USE dtasal        ! salinity data
453      !!----------------------------------------------------------------------
454
455      IF ( lk_mpp ) CALL mppsync
456
457      ! 1. Unit close
458      ! -------------
459
460      CLOSE( numnam )           ! namelist
461      CLOSE( numout )           ! standard model output file
462
463      IF(lwp) CLOSE( numstp )   ! time-step file
464      IF(lwp) CLOSE( numsol )
465
466   END SUBROUTINE opa_closefile
467
468   !!======================================================================
469END MODULE opa
Note: See TracBrowser for help on using the repository browser.