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 @ 531

Last change on this file since 531 was 531, checked in by opalod, 18 years ago

nemo_v1_update_75 : CT : enables bit comparison between single and multiple processor runs adding nbit_cmp namelist parameter

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