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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OFF_SRC/opa.F90 @ 2281

Last change on this file since 2281 was 2281, checked in by smasson, 14 years ago

set proper svn properties to all files...

  • Property svn:keywords set to Id
File size: 16.6 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    (ldf_tra_init routine)
24   USE ldfslp          ! slopes of neutral surfaces     (ldf_slp_init routine)
25   USE traqsr          ! solar radiation penetration    (tra_qsr_init routine)
26   USE trabbl          ! bottom boundary layer          (tra_bbl_init routine)
27   USE zpshde          ! partial step: hor. derivative  (zps_hde_init routine)
28   USE zdfini
29   USE zdfddm
30   USE zdfkpp
31
32   USE phycst          ! physical constant                  (par_cst routine)
33   USE dtadyn          ! Lecture and Interpolation of the dynamical fields
34   USE trcini          ! Initilization of the passive tracers
35   USE stpctl
36   USE daymod          ! calendar                         (day     routine)
37   USE trcstp          ! passive tracer time-stepping      (trc_stp routine)
38   USE dtadyn          ! Lecture and interpolation of the dynamical fields
39   USE stpctl          ! time stepping control            (stp_ctl routine)
40
41   USE iom
42#if defined key_iomput
43   USE  mod_ioclient
44#endif
45
46   IMPLICIT NONE
47   PRIVATE
48
49   !! * Module variables
50   CHARACTER (len=64) ::        &
51      cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
52
53   !! * Routine accessibility
54   PUBLIC opa_model      ! called by model.F90
55   PUBLIC opa_init
56   !!----------------------------------------------------------------------
57   !!   OPA 9.0 , LOCEAN-IPSL  (2005)
58   !!   $Id$
59   !!   This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
60   !!----------------------------------------------------------------------
61
62CONTAINS
63
64   SUBROUTINE opa_model
65      !!----------------------------------------------------------------------
66      !!                     ***  ROUTINE opa  ***
67      !!
68      !! ** Purpose :   opa solves the primitive equations on an orthogonal
69      !!      curvilinear mesh on the sphere.
70      !!
71      !! ** Method  : - model general initialization
72      !!              - launch the time-stepping (stp routine)
73      !!
74      !! References :
75      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
76      !!              internal report, IPSL.
77      !!----------------------------------------------------------------------
78      INTEGER :: istp, indic       ! time step index
79      !!----------------------------------------------------------------------
80
81      CALL opa_init  ! Initializations
82
83      IF( lk_mpp )   CALL mpp_max( nstop )
84
85      ! check that all process are still there... If some process have an error,
86      ! they will never enter in step and other processes will wait until the end of the cpu time!
87      IF( lk_mpp )   CALL mpp_max( nstop )
88
89      istp = nit000
90         !
91      DO WHILE ( istp <= nitend .AND. nstop == 0 )
92         !
93         IF( istp /= nit000 )   CALL day      ( istp )   ! Calendar (day was already called at nit000 in day_init)
94                                CALL iom_setkt( istp )   ! say to iom that we are at time step kstp
95                                CALL dta_dyn  ( istp )   ! Interpolation of the dynamical fields
96                                CALL trc_stp  ( istp )   ! time-stepping
97                                CALL stp_ctl  ( istp, indic )   ! Time loop: control and print
98         istp = istp + 1
99         IF( lk_mpp )   CALL mpp_max( nstop )
100      END DO
101      !                                     ! ========= !
102      !                                     !  Job end  !
103      !                                     ! ========= !
104
105      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
106
107      IF( nstop /= 0 .AND. lwp ) THEN                 ! error print
108         WRITE(numout,cform_err)
109         WRITE(numout,*) nstop, ' error have been found'
110      ENDIF
111
112      CALL opa_closefile
113
114      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp)
115      !
116   END SUBROUTINE opa_model
117
118
119   SUBROUTINE opa_init
120      !!----------------------------------------------------------------------
121      !!                     ***  ROUTINE opa_init ***
122      !!
123      !! ** Purpose :   opa solves the primitive equations on an orthogonal
124      !!      curvilinear mesh on the sphere.
125      !!
126      !! ** Method  : - model general initialization
127      !!
128      !! References :
129      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
130      !!              internal report, IPSL.
131      !!
132      !! History :
133      !!   4.0  !  90-10  (C. Levy, G. Madec)  Original code
134      !!   7.0  !  91-11  (M. Imbard, C. Levy, G. Madec)
135      !!   7.1  !  93-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
136      !!                   M. Guyon, A. Lazar, P. Delecluse, C. Perigaud,
137      !!                   G. Caniaux, B. Colot, C. Maes ) release 7.1
138      !!        !  92-06  (L.Terray) coupling implementation
139      !!        !  93-11  (M.A. Filiberti) IGLOO sea-ice
140      !!   8.0  !  96-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
141      !!                   M. Guyon, A. Lazar, P. Delecluse, L.Terray,
142      !!                   M.A. Filiberti, J. Vialar, A.M. Treguier,
143      !!                   M. Levy)  release 8.0
144      !!   8.1  !  97-06  (M. Imbard, G. Madec)
145      !!   8.2  !  99-11  (M. Imbard, H. Goosse)  LIM sea-ice model
146      !!        !  99-12  (V. Thierry, A-M. Treguier, M. Imbard, M-A. Foujols)  OPEN-MP
147      !!        !  00-07  (J-M Molines, M. Imbard)  Open Boundary Conditions  (CLIPPER)
148      !!   9.0  !  02-08  (G. Madec)  F90: Free form and modules
149      !!----------------------------------------------------------------------
150      !! * Local declarations
151#if defined key_oasis3 || defined key_oasis4 || defined key_iomput
152      INTEGER :: ilocal_comm
153#endif
154      CHARACTER(len=80),dimension(10) ::   cltxt = ''
155      INTEGER                         ::   ji   ! local loop indices
156      !!
157      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   &
158         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle, nn_bench
159      !!----------------------------------------------------------------------
160
161      !
162      !                             ! open Namelist file     
163      CALL ctl_opn( numnam, 'namelist', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. )
164      !
165      READ( numnam, namctl )        ! Namelist namctl : Control prints & Benchmark
166      !
167      !                             !--------------------------------------------!
168      !                             !  set communicator & select the local node  !
169      !                             !--------------------------------------------!
170#if defined key_iomput
171# if defined key_oasis3 || defined key_oasis4   
172      CALL cpl_prism_init( ilocal_comm )      ! nemo local communicator given by oasis
173      CALL init_ioclient()                    ! io_server will get its communicators (if needed) from oasis (we don't see it)
174# else
175      CALL init_ioclient( ilocal_comm )       ! nemo local communicator (used or not) given by the io_server
176# endif
177      narea = mynode( cltxt, ilocal_comm )    ! Nodes selection
178
179#else
180# if defined key_oasis3 || defined key_oasis4   
181      CALL cpl_prism_init( ilocal_comm )      ! nemo local communicator given by oasis
182      narea = mynode( cltxt, ilocal_comm )    ! Nodes selection (control print return in cltxt)
183# else
184      narea = mynode( cltxt )                 ! Nodes selection (control print return in cltxt)
185# endif
186#endif
187      narea = narea + 1                       ! mynode return the rank of proc (0 --> jpnij -1 )
188
189      lwp = (narea == 1) .OR. ln_ctl          ! control of all listing output print
190
191      IF(lwp) THEN                            ! open listing units
192         !
193         CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
194         !
195         WRITE(numout,*)
196         WRITE(numout,*) '         CNRS - NERC - Met OFFICE - MERCATOR-ocean'
197         WRITE(numout,*) '                       NEMO team'
198         WRITE(numout,*) '            Ocean General Circulation Model'
199         WRITE(numout,*) '                  version 3.2  (2009) '
200         WRITE(numout,*)
201         WRITE(numout,*)
202         DO ji = 1, SIZE(cltxt) 
203            IF( TRIM(cltxt(ji)) /= '' )   WRITE(numout,*) cltxt(ji)      ! control print of mynode
204         END DO
205         WRITE(numout,cform_aaa)                                         ! Flag AAAAAAA
206         !
207      ENDIF
208
209      CALL opa_flg                          ! Control prints & Benchmark
210
211      !                                     ! ============================== !
212      !                                     !  Model general initialization  !
213      !                                     ! ============================== !
214
215      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
216
217                                            ! Domain decomposition
218                                            ! Domain decomposition
219      IF( jpni*jpnj == jpnij ) THEN   ;   CALL mpp_init      ! standard cutting out
220      ELSE                            ;   CALL mpp_init2     ! eliminate land processors
221      ENDIF
222
223
224
225      !                                     ! General initialization
226                            CALL     phy_cst    ! Physical constants
227                            CALL     eos_init   ! Equation of state
228                            CALL     dom_cfg    ! Domain configuration
229                            CALL     dom_init   ! Domain
230
231      IF( ln_zps        )   CALL zps_hde_init   ! Partial steps:  horizontal derivative
232                            CALL  istate_init   ! ocean initial state (Dynamics and tracers)
233
234      !                                     ! Ocean physics
235      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   &
236         &                  CALL zdf_ddm_init   ! double diffusive mixing
237#if ! defined key_degrad
238                            CALL ldf_tra_init   ! Lateral ocean tracer physics
239#endif
240      IF( lk_ldfslp )       CALL ldf_slp_init   ! slope of lateral mixing
241
242      !                                     ! Active tracers
243                            CALL tra_qsr_init   ! penetrative solar radiation qsr
244      IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme
245
246      !                                     ! Passive tracers
247                            CALL     trc_init   ! Passive tracers initialization
248      !                                     ! Dynamics
249                            CALL dta_dyn_init   ! Initialization for the dynamics
250                            CALL     iom_init       ! iom_put initialization
251
252      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
253
254   END SUBROUTINE opa_init
255
256   SUBROUTINE opa_flg
257      !!----------------------------------------------------------------------
258      !!                     ***  ROUTINE opa  ***
259      !!
260      !! ** Purpose :   Initialise logical flags that control the choice of
261      !!              some algorithm or control print
262      !!
263      !! ** Method  : - print namctl information
264      !!              - Read in namilist namflg logical flags
265      !!----------------------------------------------------------------------
266
267      IF(lwp) THEN                 ! Parameter print
268         WRITE(numout,*)
269         WRITE(numout,*) 'opa_flg: Control prints & Benchmark'
270         WRITE(numout,*) '~~~~~~~ '
271         WRITE(numout,*) '   Namelist namctl'
272         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl
273         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print
274         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls
275         WRITE(numout,*) '      End i indice for SUM control    nn_ictle   = ', nn_ictle
276         WRITE(numout,*) '      Start j indice for SUM control  nn_jctls   = ', nn_jctls
277         WRITE(numout,*) '      End j indice for SUM control    nn_jctle   = ', nn_jctle
278         WRITE(numout,*) '      number of proc. following i     nn_isplt   = ', nn_isplt
279         WRITE(numout,*) '      number of proc. following j     nn_jsplt   = ', nn_jsplt
280         WRITE(numout,*) '      benchmark parameter (0/1)       nn_bench   = ', nn_bench
281      ENDIF
282
283      nprint    = nn_print          ! convert DOCTOR namelist names into OLD names
284      nictls    = nn_ictls
285      nictle    = nn_ictle
286      njctls    = nn_jctls
287      njctle    = nn_jctle
288      isplt     = nn_isplt
289      jsplt     = nn_jsplt
290      nbench    = nn_bench
291      !                           ! Parameter control
292      !
293      IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints
294         IF( lk_mpp ) THEN
295            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real splitted domain
296         ELSE
297            IF( isplt == 1 .AND. jsplt == 1  ) THEN
298               CALL ctl_warn( ' - isplt & jsplt are equal to 1',   &
299                  &           ' - the print control will be done over the whole domain' )
300            ENDIF
301            ijsplt = isplt * jsplt            ! total number of processors ijsplt
302         ENDIF
303         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
304         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
305         !
306         !                              ! indices used for the SUM control
307         IF( nictls+nictle+njctls+njctle == 0 )   THEN    ! print control done over the default area
308            lsp_area = .FALSE.
309         ELSE                                             ! print control done over a specific  area
310            lsp_area = .TRUE.
311            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
312               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
313               nictls = 1
314            ENDIF
315            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
316               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
317               nictle = jpiglo
318            ENDIF
319            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
320               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
321               njctls = 1
322            ENDIF
323            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
324               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
325               njctle = jpjglo
326            ENDIF
327         ENDIF
328      ENDIF
329
330      IF( nbench == 1 )   THEN            ! Benchmark
331         SELECT CASE ( cp_cfg )
332         CASE ( 'gyre' )   ;   CALL ctl_warn( ' The Benchmark is activated ' )
333         CASE DEFAULT      ;   CALL ctl_stop( ' The Benchmark is based on the GYRE configuration:',   &
334            &                                 ' key_gyre must be used or set nbench = 0' )
335         END SELECT
336      ENDIF
337
338   END SUBROUTINE opa_flg
339
340   SUBROUTINE opa_closefile
341      !!----------------------------------------------------------------------
342      !!                     ***  ROUTINE opa_closefile  ***
343      !!
344      !! ** Purpose :   Close the files
345      !!
346      !! ** Method  :
347      !!
348      !! History :
349      !!   9.0  !  05-01  (O. Le Galloudec)  Original code
350      !!----------------------------------------------------------------------
351      !!----------------------------------------------------------------------
352
353      IF ( lk_mpp ) CALL mppsync
354
355      ! 1. Unit close
356      ! -------------
357
358      CLOSE( numnam )           ! namelist
359      CLOSE( numout )           ! standard model output file
360
361      IF(lwp) CLOSE( numstp )   ! time-step file
362
363      CALL iom_close            ! close all input/output files
364
365   END SUBROUTINE opa_closefile
366
367   !!======================================================================
368END MODULE opa
Note: See TracBrowser for help on using the repository browser.