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

Last change on this file since 1581 was 1581, checked in by smasson, 15 years ago

ctlopn cleanup, see ticket:515 and ticket:237

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