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/OFF_SRC – NEMO

source: trunk/NEMO/OFF_SRC/opa.F90 @ 1746

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

move daymod public variables in dom_oce, see ticket:590

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 14.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   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE dom_oce         ! ocean space domain variables
12   USE oce             ! dynamics and tracers variables
13   USE in_out_manager  ! I/O manager
14   USE lib_mpp         ! distributed memory computing
15
16   USE domcfg          ! domain configuration               (dom_cfg routine)
17   USE mppini          ! shared/distributed memory setting (mpp_init routine)
18   USE domain          ! domain initialization             (dom_init routine)
19   USE istate          ! initial state setting          (istate_init routine)
20   USE eosbn2          ! equation of state            (eos bn2 routine)
21
22   ! ocean physics
23   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine)
24   USE traqsr          ! solar radiation penetration   (tra_qsr_init routine)
25
26   USE phycst          ! physical constant                  (par_cst routine)
27   USE dtadyn          ! Lecture and Interpolation of the dynamical fields
28   USE trcini          ! Initilization of the passive tracers
29   USE step            ! OPA time-stepping                  (stp     routine)
30
31   USE iom
32#if defined key_iomput
33   USE  mod_ioclient
34#endif
35
36   IMPLICIT NONE
37   PRIVATE
38
39   !! * Module variables
40   CHARACTER (len=64) ::        &
41      cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
42
43   !! * Routine accessibility
44   PUBLIC opa_model      ! called by model.F90
45   PUBLIC opa_init
46   !!----------------------------------------------------------------------
47   !!   OPA 9.0 , LOCEAN-IPSL  (2005)
48   !!   $Id$
49   !!   This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
50   !!----------------------------------------------------------------------
51
52CONTAINS
53
54   SUBROUTINE opa_model
55      !!----------------------------------------------------------------------
56      !!                     ***  ROUTINE opa  ***
57      !!
58      !! ** Purpose :   opa solves the primitive equations on an orthogonal
59      !!      curvilinear mesh on the sphere.
60      !!
61      !! ** Method  : - model general initialization
62      !!              - launch the time-stepping (stp routine)
63      !!
64      !! References :
65      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
66      !!              internal report, IPSL.
67      !!----------------------------------------------------------------------
68      INTEGER ::   istp       ! time step index
69      !!----------------------------------------------------------------------
70
71      CALL opa_init  ! Initializations
72
73      IF( lk_mpp )   CALL mpp_max( nstop )
74
75      ! check that all process are still there... If some process have an error,
76      ! they will never enter in step and other processes will wait until the end of the cpu time!
77      IF( lk_mpp )   CALL mpp_max( nstop )
78
79      istp = nit000
80         !
81      DO WHILE ( istp <= nitend .AND. nstop == 0 )
82         CALL stp( istp )
83         istp = istp + 1
84         IF( lk_mpp )   CALL mpp_max( nstop )
85      END DO
86      !                                     ! ========= !
87      !                                     !  Job end  !
88      !                                     ! ========= !
89
90      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
91
92      IF( nstop /= 0 .AND. lwp ) THEN                 ! error print
93         WRITE(numout,cform_err)
94         WRITE(numout,*) nstop, ' error have been found'
95      ENDIF
96
97      CALL opa_closefile
98
99      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp)
100      !
101   END SUBROUTINE opa_model
102
103
104   SUBROUTINE opa_init
105      !!----------------------------------------------------------------------
106      !!                     ***  ROUTINE opa_init ***
107      !!
108      !! ** Purpose :   opa solves the primitive equations on an orthogonal
109      !!      curvilinear mesh on the sphere.
110      !!
111      !! ** Method  : - model general initialization
112      !!
113      !! References :
114      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
115      !!              internal report, IPSL.
116      !!
117      !! History :
118      !!   4.0  !  90-10  (C. Levy, G. Madec)  Original code
119      !!   7.0  !  91-11  (M. Imbard, C. Levy, G. Madec)
120      !!   7.1  !  93-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
121      !!                   M. Guyon, A. Lazar, P. Delecluse, C. Perigaud,
122      !!                   G. Caniaux, B. Colot, C. Maes ) release 7.1
123      !!        !  92-06  (L.Terray) coupling implementation
124      !!        !  93-11  (M.A. Filiberti) IGLOO sea-ice
125      !!   8.0  !  96-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
126      !!                   M. Guyon, A. Lazar, P. Delecluse, L.Terray,
127      !!                   M.A. Filiberti, J. Vialar, A.M. Treguier,
128      !!                   M. Levy)  release 8.0
129      !!   8.1  !  97-06  (M. Imbard, G. Madec)
130      !!   8.2  !  99-11  (M. Imbard, H. Goosse)  LIM sea-ice model
131      !!        !  99-12  (V. Thierry, A-M. Treguier, M. Imbard, M-A. Foujols)  OPEN-MP
132      !!        !  00-07  (J-M Molines, M. Imbard)  Open Boundary Conditions  (CLIPPER)
133      !!   9.0  !  02-08  (G. Madec)  F90: Free form and modules
134      !!----------------------------------------------------------------------
135      !! * Local declarations
136#if defined key_iomput
137      INTEGER :: localComm
138#endif
139      CHARACTER (len=20) ::   namelistname
140      CHARACTER (len=28) ::   file_out
141      NAMELIST/namctl/ ln_ctl, nprint, nictls, nictle,   &
142         &             isplt , jsplt , njctls, njctle, nbench
143
144      !!----------------------------------------------------------------------
145
146      ! Initializations
147      ! ===============
148
149      file_out = 'ocean.output'
150
151      ! open listing and namelist units
152      CALL ctlopn( numout, file_out, 'UNKNOWN', 'FORMATTED',   &
153         &         'SEQUENTIAL', 1, 6, .FALSE., 1 )
154
155      namelistname = 'namelist'
156      CALL ctlopn( numnam, namelistname, 'OLD', 'FORMATTED', 'SEQUENTIAL',   &
157         &         1, numout, .FALSE., 1 )
158
159      WRITE(numout,*)
160      WRITE(numout,*) '                 L O D Y C - I P S L'
161      WRITE(numout,*) '                     O P A model'
162      WRITE(numout,*) '            Ocean General Circulation Model'
163      WRITE(numout,*) '               version OPA 9.0  (2005) '
164      WRITE(numout,*)
165      WRITE(numout,*)
166
167      ! Namelist namctl : Control prints & Benchmark
168      REWIND( numnam )
169      READ  ( numnam, namctl )
170
171#if defined key_iomput
172      CALL init_ioclient(localcomm)
173      narea = mynode(localComm)
174#else
175      ! Nodes selection
176      narea = mynode()
177#endif
178
179      ! Nodes selection
180      narea = narea + 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="('ocean.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      CALL opa_flg                          ! Control prints & Benchmark
203
204      !                                     ! ============================== !
205      !                                     !  Model general initialization  !
206      !                                     ! ============================== !
207
208      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
209
210                                            ! Domain decomposition
211      IF( jpni * jpnj == jpnij ) THEN
212         CALL mpp_init                          ! standard cutting out
213      ELSE
214         CALL mpp_init2                         ! eliminate land processors
215      ENDIF
216     
217      CALL phy_cst                          ! Physical constants
218
219      CALL eos_init                         ! Equation of state
220
221      CALL dom_cfg                          ! Domain configuration
222
223      CALL dom_init                         ! Domain
224
225      CALL istate_init                      ! ocean initial state (Dynamics and tracers)
226     
227      CALL dta_dyn( nit000 )                 ! Initialization for the dynamics
228     
229      CALL trc_ini                           ! Passive tracers
230      !                                     ! Ocean physics
231      CALL tra_qsr_init                         ! Solar radiation penetration
232
233#if ! defined key_off_degrad
234      CALL ldf_tra_init                         ! Lateral ocean tracer physics
235#endif
236      CALL iom_init( fjulday - adatrj )     ! iom_put initialization
237      !                                     ! =============== !
238      !                                     !  time stepping  !
239      !                                     ! =============== !
240
241      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
242
243   END SUBROUTINE opa_init
244
245   SUBROUTINE opa_flg
246      !!----------------------------------------------------------------------
247      !!                     ***  ROUTINE opa  ***
248      !!
249      !! ** Purpose :   Initialize logical flags that control the choice of
250      !!      some algorithm or control print
251      !!
252      !! ** Method  :    Read in namilist namflg logical flags
253      !!
254      !! History :
255      !!   9.0  !  03-11  (G. Madec)  Original code
256      !!----------------------------------------------------------------------
257      !! * Local declarations
258
259      ! Parameter control and print
260      ! ---------------------------
261      IF(lwp) THEN
262         WRITE(numout,*)
263         WRITE(numout,*) 'opa_flg: Control prints & Benchmark'
264         WRITE(numout,*) '~~~~~~~ '
265         WRITE(numout,*) '          Namelist namctl'
266         WRITE(numout,*) '             run control (for debugging)     ln_ctl    = ', ln_ctl
267         WRITE(numout,*) '             level of print                  nprint    = ', nprint
268         WRITE(numout,*) '             Start i indice for SUM control  nictls    = ', nictls
269         WRITE(numout,*) '             End i indice for SUM control    nictle    = ', nictle
270         WRITE(numout,*) '             Start j indice for SUM control  njctls    = ', njctls
271         WRITE(numout,*) '             End j indice for SUM control    njctle    = ', njctle
272         WRITE(numout,*) '             number of proc. following i     isplt     = ', isplt
273         WRITE(numout,*) '             number of proc. following j     jsplt     = ', jsplt
274         WRITE(numout,*) '             benchmark parameter (0/1)       nbench    = ', nbench
275      ENDIF
276
277      ! ... Control the sub-domain area indices for the control prints
278      IF( ln_ctl )   THEN
279         IF( lk_mpp )   THEN
280            ! the domain is forced to the real splitted domain in MPI
281            isplt = jpni ; jsplt = jpnj ; ijsplt = jpni*jpnj
282         ELSE
283            IF( isplt == 1 .AND. jsplt == 1  ) THEN
284               CALL ctl_warn( '          - isplt & jsplt are equal to 1',   &
285                    &         '          - the print control will be done over the whole domain' )
286            ENDIF
287
288            ! compute the total number of processors ijsplt
289            ijsplt = isplt*jsplt
290         ENDIF
291
292         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
293         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
294
295         ! Control the indices used for the SUM control
296         IF( nictls+nictle+njctls+njctle == 0 )   THEN
297            ! the print control is done over the default area
298            lsp_area = .FALSE.
299         ELSE
300            ! the print control is done over a specific  area
301            lsp_area = .TRUE.
302            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
303               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
304               nictls = 1
305            ENDIF
306
307            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
308               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
309               nictle = jpiglo
310            ENDIF
311
312            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
313               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
314               njctls = 1
315            ENDIF
316
317            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
318               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
319               njctle = jpjglo
320            ENDIF
321
322         ENDIF          ! IF( nictls+nictle+njctls+njctle == 0 )
323       ENDIF            ! IF(ln_ctl)
324
325      IF( nbench == 1 )   THEN
326         SELECT CASE ( cp_cfg )
327         CASE ( 'gyre' )
328            CALL ctl_warn( '          The Benchmark is activated ' )
329         CASE DEFAULT
330            CALL ctl_stop( '          The Benchmark is based on the GYRE configuration: key_gyre must &
331               &                      be used or set nbench = 0' )
332         END SELECT
333      ENDIF
334
335   END SUBROUTINE opa_flg
336
337   SUBROUTINE opa_closefile
338      !!----------------------------------------------------------------------
339      !!                     ***  ROUTINE opa_closefile  ***
340      !!
341      !! ** Purpose :   Close the files
342      !!
343      !! ** Method  :
344      !!
345      !! History :
346      !!   9.0  !  05-01  (O. Le Galloudec)  Original code
347      !!----------------------------------------------------------------------
348      !!----------------------------------------------------------------------
349
350      IF ( lk_mpp ) CALL mppsync
351
352      ! 1. Unit close
353      ! -------------
354
355      CLOSE( numnam )           ! namelist
356      CLOSE( numout )           ! standard model output file
357
358      IF(lwp) CLOSE( numstp )   ! time-step file
359
360      CALL iom_close            ! close all input/output files
361
362   END SUBROUTINE opa_closefile
363
364   !!======================================================================
365END MODULE opa
Note: See TracBrowser for help on using the repository browser.