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 trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/opa.F90 @ 599

Last change on this file since 599 was 599, checked in by opalod, 17 years ago

nemo_v2_bugfix_007 : CT : correct cpp key syntax (key_oasis3, key_oasis4) to avoid messages at compilation process on NEC

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